[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-27 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #25 from CVS Commits  ---
The master branch has been updated by Mikael Morin :

https://gcc.gnu.org/g:6a460a2007dd9c527c5f9d5bbbedb852db7c1373

commit r12-8281-g6a460a2007dd9c527c5f9d5bbbedb852db7c1373
Author: Mikael Morin 
Date:   Wed Apr 27 11:36:16 2022 +0200

fortran: Compare non-constant bound expressions. [PR105379]

Starting with r12-8235-gfa5cd7102da676dcb1757b1288421f5f3439ae0e,
class descriptor types are compared to detect duplicate declarations.

This caused ICEs as the comparison of array spec supported only constant
explicit bounds, but dummy class variable descriptor types can have a
_data field with non-constant array spec bounds.

This change adds support for non-constant bounds.  For that,
gfc_dep_compare_expr is used.  It does probably more than strictly
necessary, but using it avoids rewriting a specific comparison function,
making mistakes and forgetting cases.

PR fortran/103662
PR fortran/105379

gcc/fortran/ChangeLog:

* array.cc (compare_bounds): Use bool as return type.
Support non-constant expressions.
(gfc_compare_array_spec): Update call to compare_bounds.

gcc/testsuite/ChangeLog:

* gfortran.dg/class_dummy_8.f90: New test.
* gfortran.dg/class_dummy_9.f90: New test.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-26 Thread hubicka at kam dot mff.cuni.cz via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #24 from hubicka at kam dot mff.cuni.cz ---
Thanks a lot!
Honza

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-26 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #23 from CVS Commits  ---
The master branch has been updated by Jakub Jelinek :

https://gcc.gnu.org/g:22c24ba48a20a4944a50cca06449debed7d1b3f4

commit r12-8260-g22c24ba48a20a4944a50cca06449debed7d1b3f4
Author: Jakub Jelinek 
Date:   Tue Apr 26 09:17:32 2022 +0200

testsuite: Improve unlimited_polymorphic_3.f03 [PR103662]

On Mon, Apr 25, 2022 at 01:38:25PM +0200, Mikael Morin wrote:
> I have just pushed the attached fix for two UNRESOLVED checks at -O0 that
I
> hadnât seen.

I don't like forcing of DSE in -O0 compilation, wouldn't it be better
to just not check the dse dump at -O0 like in the following patch?

Even better would be to check that the z._data = stores are both present
in *.optimized dump, but that doesn't really work at -O2 or above because
we inline the functions and optimize it completely away (both the stores
and corresponding reads).

The first hunk is needed so that __OPTIMIZE__ effective target works in
Fortran testsuite, otherwise one gets a pedantic error and __OPTIMIZE__
is considered not to match at all.

2022-04-26  Jakub Jelinek  

PR fortran/103662
* lib/target-supports.exp (check_effective_target___OPTIMIZE__):
Add
a var definition to avoid pedwarn about empty translation unit.
* gfortran.dg/unlimited_polymorphic_3.f03: Remove -ftree-dse from
dg-additional-options, guard scan-tree-dump-not directives on
__OPTIMIZE__ target.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-25 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #22 from CVS Commits  ---
The master branch has been updated by Mikael Morin :

https://gcc.gnu.org/g:6cc26f3037a18b9a958b4ac2a1363149a7fccd39

commit r12-8243-g6cc26f3037a18b9a958b4ac2a1363149a7fccd39
Author: Mikael Morin 
Date:   Mon Apr 25 13:14:20 2022 +0200

testsuite: add additional option to force DSE execution [PR103662]

This fixes a dump tree match check that is UNRESOLVED with the -O0
optimization option, as the optimization pass corresponding to the
dump file is not run at -O0, and the dump is not generated.

PR fortran/103662

gcc/testsuite/ChangeLog:

* gfortran.dg/unlimited_polymorphic_3.f03: Force execution of
the DSE optimization pass.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-25 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Richard Biener  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #21 from Richard Biener  ---
Fixed.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-24 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #20 from CVS Commits  ---
The master branch has been updated by Mikael Morin :

https://gcc.gnu.org/g:fa5cd7102da676dcb1757b1288421f5f3439ae0e

commit r12-8235-gfa5cd7102da676dcb1757b1288421f5f3439ae0e
Author: Mikael Morin 
Date:   Sun Apr 24 15:05:41 2022 +0200

fortran: Detect duplicate unlimited polymorphic types [PR103662]

This fixes a type-based alias analysis issue with unlimited polymorphic
class descriptors (types behind class(*)) causing data initialisation to
be removed by optimization.

The fortran front-end may create multiple declarations for types, for
example if a type is redeclared in each program unit it is used in.
To avoid optimization seeing them as non-aliasing, a list of derived
types is created at resolution time, and used at translation to set
the same TYPE_CANONICAL type for each duplicate type declaration.

This mechanism didnât work for unlimited polymorphic descriptors types,
as there is a short-circuit return skipping all the resolution handling
for them, including the type registration.

This change adds type registration at the short-circuit return, and
updates type comparison to handle specifically unlimited polymorphic
fake symbols, class descriptor types and virtual table types.

The test, which exhibited mismatching dynamic types had to be fixed as
well.

PR fortran/103662

gcc/fortran/ChangeLog:

* interface.cc (gfc_compare_derived_types): Support comparing
unlimited polymorphic fake symbols.  Recursively compare class
descriptor types and virtual table types.
* resolve.cc (resolve_fl_derived): Add type to the types list
on unlimited polymorphic short-circuit return.

gcc/testsuite/ChangeLog:

* gfortran.dg/unlimited_polymorphic_3.f03 (foo): Separate
bind(c) and sequence checks to...
(foo_bc, foo_sq): ... two different procedures.
(main, foo*): Change type declarations so that type name,
component name, and either bind(c) or sequence attribute match
between the main type declarations and the procedure type
declarations.
(toplevel): Add optimization dump checks.

Co-Authored-By: Jakub Jelinek 

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-20 Thread hubicka at kam dot mff.cuni.cz via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #19 from hubicka at kam dot mff.cuni.cz ---
> I agree with Jakub that this is good progression so we should probably get 
> this
> to a shape that is committable and commit it.
> 
> Btw - thanks for working on the Fortran frontend issues!
Indeed! This bug was haunting me for a while :)

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-19 Thread jakub at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #18 from Jakub Jelinek  ---
! { dg-do run }
!
! Check that pointer assignments allowed by F2003:C717
! work and check null initialization of CLASS(*) pointers.
!
! Contributed by Tobias Burnus 
!
program main
  interface
subroutine foo(z)
  class(*), pointer, intent(in) :: z
end subroutine foo
  end interface
  type sq
sequence
integer :: i
  end type sq
  type(sq), target :: x
  class(*), pointer :: y, z
  x%i = 42
  y => x
  z => y ! unlimited => unlimited allowed
  call foo (z)
  call bar
contains
  subroutine bar
type t
end type t
type(t), pointer :: x
class(*), pointer :: ptr1 => null() ! pointer initialization
if (same_type_as (ptr1, x) .neqv. .FALSE.) STOP 1
  end subroutine bar

end program main


subroutine foo(tgt)
  class(*), pointer, intent(in) :: tgt
  type sq
sequence
integer :: i
  end type sq
  type(sq), pointer :: ptr
  ptr => tgt ! sequence type => unlimited allowed
  if (ptr%i .ne. 42) STOP 2
end subroutine foo

works with your patch and doesn't without it.
But, if I change sq in foo to s, it doesn't work anymore.  Though, seems even
type name and all member names are important, so I think we should just
change the testcase to the above and perhaps add another one with bind(c)
derived type instead of the sequence one.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-19 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #17 from Mikael Morin  ---
(In reply to Jakub Jelinek from comment #15)
> Now, the question is what is the Fortran unlimited polymorphic semantics, if
> one can store through one type and read through a different type which just
> has the same layout, or if it also has to use the same name etc., or if it
> is even acceptable to store through say a type with a pair of integers and
> read through a type with double precision etc.

I think the pointer assignments in foo are invalid:


10.2.2.3 Data pointer assignment
… If the pointer object is of a type with the BIND attribute or the SEQUENCE
attribute, the dynamic type of the pointer target shall be that type.

 => the dynamic type of tgt shall be respectively s and t

7.3.2.3 CLASS type specifier
… The dynamic type of an associated polymorphic pointer is the dynamic type of
its target.

 => the dynamic type of tgt is that of z
 => the dynamic type of z is that of y
 => the dynamic type of y is that of x, which is sq

7.5.2.4 Determination of derived types
… Data entities also have the same type if they are declared with reference to
different derived-type definitions that specify the same type name, all have
the SEQUENCE attribute or all have the BIND attribute, have no components with
PRIVATE accessibility, and have components that agree in order, name, and
attributes. Otherwise, they are of different derived types.

 => sq and s are different types (different component name)
 => sq and t are different types (different component name, bind(c), sequence)
 => s and t are different types (bind(c), sequence)


So ptr1 and ptr2 should either have type sq, or s and t should be changed to be
"compatible" with sq. And "compatible" is defined in the 7.5.2.4 excerpt above.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-19 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #16 from Richard Biener  ---
(In reply to Mikael Morin from comment #12)
> Created attachment 52828 [details]
> Fix attempt
> 
> I think the attached patch avoids the multiple declarations for
> __class_STAR_p,
> but the testsuite FAIL remains, so I must be missing important.
> Is there a -fdump-tree-types or something so that the problem can be seen in
> dumps (both for eyeballing and for matching with the testsuite)?

I agree with Jakub that this is good progression so we should probably get this
to a shape that is committable and commit it.

Btw - thanks for working on the Fortran frontend issues!

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-19 Thread jakub at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #15 from Jakub Jelinek  ---
Putting a breakpoint on new_alias_set, I see that
RECORD_TYPE sq gets alias set 1
RECORD_TYPE s gets alias set 9
RECORD_TYPE t gets alias set 10

Those are
  type sq
sequence
integer :: i
  end type sq
and
  type, bind(c) :: s
integer (c_int) :: k
  end type s
  type t
sequence
integer :: k
  end type t
in the testcase.  The testcase stores through the sq type and reads through
pointer to s and pointer to t type.  As the alias sets are different, for the
middle-end the testcase is invalid.
Now, the question is what is the Fortran unlimited polymorphic semantics, if
one can store through one type and read through a different type which just has
the same layout, or if it also has to use the same name etc., or if it is even
acceptable to store through say a type with a pair of integers and read through
a type with double precision etc.
GCC has types that can alias anything, so if the semantics is like that,
unlimited polymorphic middle-end pointers perhaps should use that.
Or the testcase is invalid and has to use type sq in foo as well.  Or we need
to ensure sq and s/t above have the same alias set.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-19 Thread jakub at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #14 from Jakub Jelinek  ---
Looking at your patch, there is a positive change with your patch, in optimized
dump the z._data store is no longer removed:
 __attribute__((externally_visible))
 integer(kind=4) main (integer(kind=4) argc, character(kind=1) * * argv)
 {
+  struct sq x;
   struct __class__STAR_p z;
   static integer(kind=4) options.0[7] = {2116, 4095, 0, 1, 1, 0, 31};
   integer(kind=4) _7;
@@ -37,6 +38,7 @@ integer(kind=4) main (integer(kind=4) ar
[local count: 1073741824]:
   _gfortran_set_args (argc_2(D), argv_3(D));
   _gfortran_set_options (7, [0]);
+  z._data = 
   foo ();
   _7 = __vtab__STAR._hash;
   if (_7 == 58708456)
@@ -48,6 +50,7 @@ integer(kind=4) main (integer(kind=4) ar
   _gfortran_stop_numeric (1, 0);

[local count: 1073441178]:
+  x ={v} {CLOBBER(eol)};
   z ={v} {CLOBBER(eol)};
   return 0;
But yes, it is still not enough.
If I use -Os -fno-tree-dse rather than -Os with your patch, the incremental
difference in optimized dump is:
--- unlimited_polymorphic_3.f03.252t.optimized  2022-04-19 15:32:50.716092070
+0200
+++ unlimited_polymorphic_3.f03.252t.optimized  2022-04-19 15:33:07.994850946
+0200
@@ -1,4 +1,17 @@

+;; Function __copy_main_Sq (__copy_main_Sq.0, funcdef_no=2, decl_uid=4241,
cgraph_uid=2, symbol_order=2)
+
+__attribute__((fn spec (". r w ")))
+void __copy_main_Sq (struct sq & restrict src, struct sq & restrict dst)
+{
+   [local count: 1073741824]:
+  *dst_2(D) = *src_3(D);
+  return;
+
+}
+
+
+
 ;; Function foo (foo_, funcdef_no=0, decl_uid=4226, cgraph_uid=1,
symbol_order=1)

 __attribute__((fn spec (". r ")))
@@ -32,12 +45,16 @@ integer(kind=4) main (integer(kind=4) ar
 {
   struct sq x;
   struct __class__STAR_p z;
+  static struct __vtype_main_Sq __vtab_main_Sq = {._hash=85658372, ._size=4,
._extends=0B, ._def_init=&__def_init_main_Sq, ._copy=__copy_main_Sq,
._final=0B, ._deallocate=0B};
   static integer(kind=4) options.0[7] = {2116, 4095, 0, 1, 1, 0, 31};
   integer(kind=4) _7;

[local count: 1073741824]:
   _gfortran_set_args (argc_2(D), argv_3(D));
   _gfortran_set_options (7, [0]);
+  x.i = 42;
+  z._vptr = &__vtab_main_Sq;
+  z._len = 0;
   z._data = 
   foo ();
   _7 = __vtab__STAR._hash;

I think the _vptr and _len fields aren't ever read and so it is ok the stores
to them are optimized away, so I think it is the x.i = 42; store.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-18 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #13 from Mikael Morin  ---
(In reply to Mikael Morin from comment #12)
> ... so I must be missing important.

I must be missing *something* important.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-04-18 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Mikael Morin  changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #12 from Mikael Morin  ---
Created attachment 52828
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=52828=edit
Fix attempt

I think the attached patch avoids the multiple declarations for __class_STAR_p,
but the testsuite FAIL remains, so I must be missing important.
Is there a -fdump-tree-types or something so that the problem can be seen in
dumps (both for eyeballing and for matching with the testsuite)?

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-03-24 Thread jakub at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Jakub Jelinek  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #11 from Jakub Jelinek  ---
gfc_get_derived_type sets the unlimited_entity flag for these, but I guess not
all unlimited entities should have the same TYPE_CANONICAL, e.g. on
subroutine foo (a, b, c, d, e, f)
  class(*) :: a
  class(*) :: b(:)
  class(*) :: c(:, :, :)
  class(*), pointer :: d
  class(*), pointer :: e(:)
  class(*), pointer :: f(:, :)
end subroutine
there are various RECORD_TYPEs.
So just adding a single tree to use for those would be wrong, thus I think
best would be really to register the unlimited entities in the derived type
list and handle them in gfc_compare_derived_types.  But I'm afraid I don't know
enough about this stuff to do this myself.

Tobias or Paul, could you please have a look?
This is a P1 bug and therefore GCC 12 blocker.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-03-22 Thread jakub at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Jakub Jelinek  changed:

   What|Removed |Added

 CC||burnus at gcc dot gnu.org,
   ||jakub at gcc dot gnu.org

--- Comment #10 from Jakub Jelinek  ---
>From what I can see, for normal derived types resolve_symbol calls
resolve_fl_derived -> resolve_fl_derived0 -> add_dt_to_dt_list
which ensures that the derived type eventually makes it into ns->derived_types
and then gfc_get_derived_type will do:
  /* The derived types from an earlier namespace can be used as the
 canonical type.  */
  if (derived->backend_decl == NULL
  && !derived->attr.use_assoc
  && !derived->attr.used_in_submodule
  && gfc_global_ns_list)
{
  for (ns = gfc_global_ns_list;
   ns->translated && !got_canonical;
   ns = ns->sibling)
{
  if (ns->derived_types)
{
  for (gfc_symbol *dt = ns->derived_types; dt && !got_canonical;
   dt = dt->dt_next)
{
  gfc_copy_dt_decls_ifequal (dt, derived, true);
  if (derived->backend_decl)
got_canonical = true;
  if (dt->dt_next == ns->derived_types)
break;
}
}
}
}
(ugh, linear walk of all namespaces and all derived types in them!  A hash
table would be much better) will find matching derived type in some other
namespace
and if it has backend_decl, will use it as TYPE_CANONICAL.
All of resolve_symbol and resolve_fl_derived and resolve_fl_derived0 have an
early exit for sym->attr.unlimited_polymorphic,
so add_dt_to_dt_list isn't done for it but that isn't a big deal because
gfc_get_derived_type for derived->attr.unlimited_polymorphic just returns
ptr_type_node (the same in all namespaces).

But __class__STAR_p symbol isn't unlimited_polymorphic, but in
resolve_fl_derive we trigger:
  if (sym->attr.is_class && sym->ts.u.derived == NULL)
{
  /* Fix up incomplete CLASS symbols.  */
  gfc_component *data = gfc_find_component (sym, "_data", true, true,
NULL);
  gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true,
NULL);

  /* Nothing more to do for unlimited polymorphic entities.  */
  if (data->ts.u.derived->attr.unlimited_polymorphic)
return true;
and so don't call resolve_fl_derived0, neither for sym nor for vptr, so never
call add_dt_to_dt_list for __class__STAR_p
and so gfc_get_derived_type for those will always set TYPE_CANONICAL to itself,
so each namespace's __class__STAR_p is considered to be private for TBAA
purposes.

--- gcc/fortran/resolve.cc.jj   2022-03-21 11:00:06.447824689 +0100
+++ gcc/fortran/resolve.cc  2022-03-22 12:35:38.381250338 +0100
@@ -15138,7 +15138,10 @@ resolve_fl_derived (gfc_symbol *sym)

   /* Nothing more to do for unlimited polymorphic entities.  */
   if (data->ts.u.derived->attr.unlimited_polymorphic)
-   return true;
+   {
+ add_dt_to_dt_list (sym);
+ return true;
+   }
   else if (vptr->ts.u.derived == NULL)
{
  gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
doesn't help much though, while it registers __class_STAR_p,
gfc_get_derived_type -> gfc_copy_dt_decls_ifequal -> gfc_compare_derived_types
considers them unequal.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-01-18 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Richard Biener  changed:

   What|Removed |Added

   Priority|P3  |P1

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-01-17 Thread hubicka at kam dot mff.cuni.cz via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #9 from hubicka at kam dot mff.cuni.cz ---
> I'm inclined to make this P1 even though it is gfortran only.  As a last 
> resort
> it should work to make the receiver side a ref-all pointer.
Yes, I also think this is important bug (like all TBAA related wrong
codes).  Getting alias set 0 to the receiver is probably doable even
with my Fortran frontend knowledge, but I would like to understand why
the types are not matching which I don't.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-01-17 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

--- Comment #8 from Richard Biener  ---
I'm inclined to make this P1 even though it is gfortran only.  As a last resort
it should work to make the receiver side a ref-all pointer.

[Bug fortran/103662] [12 Regression] TBAA problem in Fortran FE triggering in gfortran.dg/unlimited_polymorphic_3.f03

2022-01-04 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103662

Richard Biener  changed:

   What|Removed |Added

Summary|TBAA problem in Fortran FE  |[12 Regression] TBAA
   |triggering in   |problem in Fortran FE
   |gfortran.dg/unlimited_polym |triggering in
   |orphic_3.f03|gfortran.dg/unlimited_polym
   ||orphic_3.f03
   Target Milestone|--- |12.0

--- Comment #7 from Richard Biener  ---
I'm marking it as a regression, note the "mistake" in the frontend generated
code is latent.