public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/38913]  New: Fortran does not set TYPE_CANONICAL properly
@ 2009-01-19 15:37 rguenth at gcc dot gnu dot org
  2009-01-19 16:23 ` [Bug fortran/38913] " rguenth at gcc dot gnu dot org
                   ` (19 more replies)
  0 siblings, 20 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-01-19 15:37 UTC (permalink / raw)
  To: gcc-bugs

TYPE_CANONICAL should specify a canonical type node (equivalent for type
comparison for example during TBAA) for each type declaration.  Failing to do
so causes TBAA pessimizations.

The frontend also does not properly identify equivalent types, which is
a correctness issue.  Consider (reduced from polyhedron protein)

subroutine check (string1, string2)
character (len=1) :: string1, string2
if (string1(1:1) /= string2(1:1)) call abort
end subroutine check
program foo
  character (len=1) :: str, str2
  str(1:1) = ' '
  str2(1:1) = convert_lower_case(str(1:1))
  call check(str, str2)

  contains
          function convert_lower_case (input_string) result (output_string)
          character (len=1) :: input_string, output_string
          output_string = input_string
          end function convert_lower_case

end program

the character array type used in the inline function convert_lower_case is
not connected to the character array type used in the main function.  This
causes the alias-oracle on the alias-improvements branch to consider
str.293[0] and (*str.327_132)[1]{lb: 1 sz: 1} to be non-aliasing even
if str.327_132 is initialized from str.293 via
str.327_132 = (character(kind=1)[1:1] *) &str.293; because the type used
in that conversion is from the inline function and is not equal to that
of std.293.

I believe that boils down to a similar issue as the one-decl for each
function thing.  Either GFortran has to use -fno-strict-aliasing or
needs to properly use canonical types.


-- 
           Summary: Fortran does not set TYPE_CANONICAL properly
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: blocker
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: rguenth at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
@ 2009-01-19 16:23 ` rguenth at gcc dot gnu dot org
  2009-01-21 20:22 ` pault at gcc dot gnu dot org
                   ` (18 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-01-19 16:23 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from rguenth at gcc dot gnu dot org  2009-01-19 16:23 -------
http://gcc.gnu.org/ml/gcc-patches/2009-01/msg00937.html


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
  2009-01-19 16:23 ` [Bug fortran/38913] " rguenth at gcc dot gnu dot org
@ 2009-01-21 20:22 ` pault at gcc dot gnu dot org
  2009-01-21 20:50 ` rguenth at gcc dot gnu dot org
                   ` (17 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-01-21 20:22 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2009-01-21 20:22 -------
(In reply to comment #1)
> http://gcc.gnu.org/ml/gcc-patches/2009-01/msg00937.html
> 

Richard,

I am not sure that any of the gfortran developers have the skills to deal with
this.  I read the words about canonical types and more or less understand them
but think that it would require more time than I have to implement what is
needed.

You have set the PR as P3/blocker - does that imply that you intend to attack
the problem or should we approach Jakub to do the business?

Cheers

Paul  


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
  2009-01-19 16:23 ` [Bug fortran/38913] " rguenth at gcc dot gnu dot org
  2009-01-21 20:22 ` pault at gcc dot gnu dot org
@ 2009-01-21 20:50 ` rguenth at gcc dot gnu dot org
  2009-01-25 15:25 ` dfranke at gcc dot gnu dot org
                   ` (16 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-01-21 20:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from rguenth at gcc dot gnu dot org  2009-01-21 20:50 -------
I was able to work around the issue sofar, but more analysis is still required.
I will see if I can find some time for that.


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|blocker                     |normal


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2009-01-21 20:50 ` rguenth at gcc dot gnu dot org
@ 2009-01-25 15:25 ` dfranke at gcc dot gnu dot org
  2009-02-06 13:45 ` pault at gcc dot gnu dot org
                   ` (15 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2009-01-25 15:25 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dfranke at gcc dot gnu dot org  2009-01-25 15:25 -------
*** Bug 38965 has been marked as a duplicate of this bug. ***


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |jv244 at cam dot ac dot uk


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2009-01-25 15:25 ` dfranke at gcc dot gnu dot org
@ 2009-02-06 13:45 ` pault at gcc dot gnu dot org
  2009-02-07 15:33 ` jv244 at cam dot ac dot uk
                   ` (14 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: pault at gcc dot gnu dot org @ 2009-02-06 13:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2009-02-06 13:44 -------
I guess that since Richard says that it's a problem, we had better confirm
it:-)

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2009-02-06 13:44:58
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2009-02-06 13:45 ` pault at gcc dot gnu dot org
@ 2009-02-07 15:33 ` jv244 at cam dot ac dot uk
  2009-02-07 18:50 ` rguenther at suse dot de
                   ` (13 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-02-07 15:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from jv244 at cam dot ac dot uk  2009-02-07 15:32 -------
(In reply to comment #5)
> I guess that since Richard says that it's a problem, we had better confirm
> it:-)

Do we need a bugzilla field 'confirmatio ad verecundiam' ;-)


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2009-02-07 15:33 ` jv244 at cam dot ac dot uk
@ 2009-02-07 18:50 ` rguenther at suse dot de
  2009-06-04 10:55 ` rguenth at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenther at suse dot de @ 2009-02-07 18:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from rguenther at suse dot de  2009-02-07 18:49 -------
Subject: Re:  Fortran does not set TYPE_CANONICAL
 properly

On Sat, 7 Feb 2009, jv244 at cam dot ac dot uk wrote:

> ------- Comment #6 from jv244 at cam dot ac dot uk  2009-02-07 15:32 -------
> (In reply to comment #5)
> > I guess that since Richard says that it's a problem, we had better confirm
> > it:-)
> 
> Do we need a bugzilla field 'confirmatio ad verecundiam' ;-)

Haha ;)

OTOH I am no longer convinced it is a real problem, but I also only have
some F77 skills, so no testcases with whatever Fortran calls "structs"
from me ;)

Richard.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2009-02-07 18:50 ` rguenther at suse dot de
@ 2009-06-04 10:55 ` rguenth at gcc dot gnu dot org
  2009-06-04 11:47 ` burnus at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-06-04 10:55 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from rguenth at gcc dot gnu dot org  2009-06-04 10:55 -------
The whole-file patches now expose this problem.

! { dg-do run }
! Test the fix for PR34438, in which default initializers
! forced the derived type to be static; ie. initialized once
! during the lifetime of the programme.  Instead, they should
! be initialized each time they come into scope.
!
module demo
   type myint
     integer :: bar = 42
   end type myint
end module demo

! ...who came up with this one too.
subroutine func (retval2)
  use demo
  type(myint) :: foo2 = myint (77)
  type(myint) :: retval2
  retval2 = foo2
  foo2%bar = 999
end subroutine func

subroutine other
  use demo
  interface
    subroutine func(rv2)
      use demo
      type(myint) :: rv2
   end subroutine func
  end interface
  type(myint) :: val2
  call func (val2)
  if ((val2%bar .ne. 77_4)) call abort ()

end subroutine other

! Run both tests.
  call other
 end
! { dg-final { cleanup-modules "demo M1" } }


with -O2 -fwhole-file we inline func into other and get

other ()
{
  static struct myint foo2D.1539 = {.barD.1534=77};
  static struct myint foo2D.1539 = {.barD.1534=77};
  struct myint & retval2D.1572;
  struct myint val2D.1544;
  integer(kind=4)D.8 D.1547;

<bb 2>:
  val2D.1544.barD.1542 = 42;
  retval2D.1572_6 = (struct myint &) &val2D.1544;
  *retval2D.1572_6 = foo2D.1539;
  foo2D.1539.barD.1534 = 999;
  D.1547_1 = val2D.1544.barD.1542;
  if (D.1547_1 != 77)

which looks good sofar.  But the store *retval2D.1572_6 = foo2D.1539 is
through a different struct myint than the load from val2D.1544.barD.1542
so we optimize the load to 42 -- the only visible aliasing store.

 <var_decl 0x7ffff7fcbc80 val2
    type <record_type 0x7ffff7fd1180 myint SI
        size <integer_cst 0x7ffff7ed4a50 constant 32>
        unit size <integer_cst 0x7ffff7ed46c0 constant 4>
        align 32 symtab 0 alias set 2 canonical type 0x7ffff7fd1180
        fields <field_decl 0x7ffff7fcbbe0 bar type <integer_type 0x7ffff7ee1540
integer(kind=4)>
            SI file t.f90 line 23 col 0 size <integer_cst 0x7ffff7ed4a50 32>
unit size <integer_cst 0x7ffff7ed46c0 4>
            align 32 offset_align 128
            offset <integer_cst 0x7ffff7ed46f0 constant 0>
            bit offset <integer_cst 0x7ffff7ed4f30 constant 0> context
<record_type 0x7ffff7fd1180 myint>>
        pointer_to_this <pointer_type 0x7ffff7fd1300> chain <type_decl
0x7ffff7fd1240 D.1543>>
    addressable used SI file t.f90 line 30 col 0 size <integer_cst
0x7ffff7ed4a50 32> unit size <integer_cst 0x7ffff7ed46c0 4>
    align 32 context <function_decl 0x7ffff5f3f200 other>>

and

 <indirect_ref 0x7ffff7ff9dc0
    type <record_type 0x7ffff7fced80 myint SI
        size <integer_cst 0x7ffff7ed4a50 constant 32>
        unit size <integer_cst 0x7ffff7ed46c0 constant 4>
        align 32 symtab 0 alias set 4 canonical type 0x7ffff7fced80
        fields <field_decl 0x7ffff7fcbaa0 bar type <integer_type 0x7ffff7ee1540
integer(kind=4)>
            SI file t.f90 line 15 col 0 size <integer_cst 0x7ffff7ed4a50 32>
unit size <integer_cst 0x7ffff7ed46c0 4>
            align 32 offset_align 128
            offset <integer_cst 0x7ffff7ed46f0 constant 0>
            bit offset <integer_cst 0x7ffff7ed4f30 constant 0> context
<record_type 0x7ffff7fced80 myint>>
        reference_to_this <reference_type 0x7ffff7fcef00> chain <type_decl
0x7ffff7fcee40 D.1535>>

    arg 0 <ssa_name 0x7ffff5f4a060
        type <reference_type 0x7ffff7fcef00 type <record_type 0x7ffff7fced80
myint>
            public unsigned DI
            size <integer_cst 0x7ffff7ed4b40 constant 64>
            unit size <integer_cst 0x7ffff7ed4b70 constant 8>
            align 64 symtab 0 alias set -1 canonical type 0x7ffff7fcef00>
        visited var <var_decl 0x7ffff5f46780 retval2>def_stmt retval2_6 =
(struct myint &) &val2;

        version 6
        ptr-info 0x7ffff7f9ac10>>

so the Frontend misses proper type unification.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2009-06-04 10:55 ` rguenth at gcc dot gnu dot org
@ 2009-06-04 11:47 ` burnus at gcc dot gnu dot org
  2009-06-04 11:49 ` rguenther at suse dot de
                   ` (10 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-06-04 11:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from burnus at gcc dot gnu dot org  2009-06-04 11:47 -------
Cf. also thread at http://gcc.gnu.org/ml/fortran/2009-06/msg00057.html

(Maybe if -fwhole-file is the permanent default and this problem is fixed, the
hack at http://gcc.gnu.org/ml/gcc-patches/2009-01/msg00937.html can be removed
...)


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2009-06-04 11:47 ` burnus at gcc dot gnu dot org
@ 2009-06-04 11:49 ` rguenther at suse dot de
  2009-06-04 12:52 ` burnus at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenther at suse dot de @ 2009-06-04 11:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from rguenther at suse dot de  2009-06-04 11:49 -------
Subject: Re:  Fortran does not set TYPE_CANONICAL
 properly

On Thu, 4 Jun 2009, burnus at gcc dot gnu dot org wrote:

> ------- Comment #9 from burnus at gcc dot gnu dot org  2009-06-04 11:47 -------
> Cf. also thread at http://gcc.gnu.org/ml/fortran/2009-06/msg00057.html
> 
> (Maybe if -fwhole-file is the permanent default and this problem is fixed, the
> hack at http://gcc.gnu.org/ml/gcc-patches/2009-01/msg00937.html can be removed
> ...)

That hack is already gone ... ;)

Richard.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2009-06-04 11:49 ` rguenther at suse dot de
@ 2009-06-04 12:52 ` burnus at gcc dot gnu dot org
  2009-06-04 13:39 ` rguenther at suse dot de
                   ` (8 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-06-04 12:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from burnus at gcc dot gnu dot org  2009-06-04 12:51 -------
(In reply to comment #10)
> That hack is already gone ... ;)
The truck hack yes, the question is whether one can also do something about the
following? Or is this a wider problem?

  /* ???  Array types are not properly unified in all cases as we have
     spurious changes in the index types for example.  Removing this
     causes all sorts of problems with the Fortran frontend.  */
  if (TREE_CODE (type1) == ARRAY_TYPE
      && TREE_CODE (type2) == ARRAY_TYPE)
    return -1;


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2009-06-04 12:52 ` burnus at gcc dot gnu dot org
@ 2009-06-04 13:39 ` rguenther at suse dot de
  2009-06-28 16:56 ` rguenth at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenther at suse dot de @ 2009-06-04 13:39 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from rguenther at suse dot de  2009-06-04 13:39 -------
Subject: Re:  Fortran does not set TYPE_CANONICAL
 properly

On Thu, 4 Jun 2009, burnus at gcc dot gnu dot org wrote:

> ------- Comment #11 from burnus at gcc dot gnu dot org  2009-06-04 12:51 -------
> (In reply to comment #10)
> > That hack is already gone ... ;)
> The truck hack yes, the question is whether one can also do something about the
> following? Or is this a wider problem?
> 
>   /* ???  Array types are not properly unified in all cases as we have
>      spurious changes in the index types for example.  Removing this
>      causes all sorts of problems with the Fortran frontend.  */
>   if (TREE_CODE (type1) == ARRAY_TYPE
>       && TREE_CODE (type2) == ARRAY_TYPE)
>     return -1;

It's a wider problem.  It's char[1:1] vs. char where the FE is
very inconsistent, also char[1:] vs. char[1:1], etc.

Probably not worth fixing.  Maybe after everything else is ...

Richard.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2009-06-04 13:39 ` rguenther at suse dot de
@ 2009-06-28 16:56 ` rguenth at gcc dot gnu dot org
  2009-06-28 20:44 ` rguenth at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-06-28 16:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from rguenth at gcc dot gnu dot org  2009-06-28 16:56 -------
Similar case, from reduced import.f90:

subroutine bar(x)
  type myType
    sequence
    integer :: i
  end type myType
  type(myType) :: x
  x%i = 5
end subroutine bar

program foo
  integer, parameter :: dp = 8
  type myType
    sequence
    integer :: i
  end type myType
  interface
    subroutine bar(x)
      import
      type(myType) :: x
    end subroutine bar
  end interface

  type(myType) :: y
  y%i = 2
  call bar(y)
  if(y%i /= 5) call abort()
end program foo


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (12 preceding siblings ...)
  2009-06-28 16:56 ` rguenth at gcc dot gnu dot org
@ 2009-06-28 20:44 ` rguenth at gcc dot gnu dot org
  2009-08-03 10:11 ` jv244 at cam dot ac dot uk
                   ` (5 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-06-28 20:44 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from rguenth at gcc dot gnu dot org  2009-06-28 20:43 -------
Another one, reduced from function_module_1.f90:

module M1

INTEGER p

CONTAINS
subroutine AA ()
   implicit NONE
   p = 1
end subroutine
end module

program P1
  USE M1
  implicit none
  p = 0
  call AA ()
  if (p /= 1) call abort
end

where the issue is that p is not properly unified in the use in P1 and AA.
After inlining we see:

p1 ()
{
  integer(kind=4)D.3 p.0D.1516;

<bb 2>:
  pD.1514 = 0;
  pD.1509 = 1;
  p.0D.1516_1 = pD.1514;
  if (p.0D.1516_1 != 1)

so we store to / read from different variables.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (13 preceding siblings ...)
  2009-06-28 20:44 ` rguenth at gcc dot gnu dot org
@ 2009-08-03 10:11 ` jv244 at cam dot ac dot uk
  2009-09-22 15:45 ` rguenth at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-08-03 10:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #15 from jv244 at cam dot ac dot uk  2009-08-03 10:11 -------
testcases in comment #13 and comment #14 pass with current trunk. The testcase
in comment #8 still fails.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (14 preceding siblings ...)
  2009-08-03 10:11 ` jv244 at cam dot ac dot uk
@ 2009-09-22 15:45 ` rguenth at gcc dot gnu dot org
  2009-10-11 12:49 ` jv244 at cam dot ac dot uk
                   ` (3 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2009-09-22 15:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #16 from rguenth at gcc dot gnu dot org  2009-09-22 15:44 -------
Re-confirmed with current trunk, testcase from (comment #8).


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|2009-02-06 13:44:58         |2009-09-22 15:44:58
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (15 preceding siblings ...)
  2009-09-22 15:45 ` rguenth at gcc dot gnu dot org
@ 2009-10-11 12:49 ` jv244 at cam dot ac dot uk
  2009-12-09 11:50 ` jv244 at cam dot ac dot uk
                   ` (2 subsequent siblings)
  19 siblings, 0 replies; 23+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-10-11 12:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #17 from jv244 at cam dot ac dot uk  2009-10-11 12:49 -------
FYI, the testcase in comment #8 fails for '-O2 -fwhole-file' but not with '-O2
-flto', even though the latter option implies the first. 


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (16 preceding siblings ...)
  2009-10-11 12:49 ` jv244 at cam dot ac dot uk
@ 2009-12-09 11:50 ` jv244 at cam dot ac dot uk
  2010-06-09 22:11 ` fxcoudert at gcc dot gnu dot org
  2010-07-24 18:12 ` jv244 at cam dot ac dot uk
  19 siblings, 0 replies; 23+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-12-09 11:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #18 from jv244 at cam dot ac dot uk  2009-12-09 11:49 -------
still fails with current trunk


-- 

jv244 at cam dot ac dot uk changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|2009-09-22 15:44:58         |2009-12-09 11:49:44
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (17 preceding siblings ...)
  2009-12-09 11:50 ` jv244 at cam dot ac dot uk
@ 2010-06-09 22:11 ` fxcoudert at gcc dot gnu dot org
  2010-07-24 18:12 ` jv244 at cam dot ac dot uk
  19 siblings, 0 replies; 23+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2010-06-09 22:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #19 from fxcoudert at gcc dot gnu dot org  2010-06-09 22:11 -------
(In reply to comment #16)
> Re-confirmed with current trunk, testcase from (comment #8).

I think it now passes.


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |fxcoudert at gcc dot gnu dot
                   |                            |org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
  2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
                   ` (18 preceding siblings ...)
  2010-06-09 22:11 ` fxcoudert at gcc dot gnu dot org
@ 2010-07-24 18:12 ` jv244 at cam dot ac dot uk
  19 siblings, 0 replies; 23+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-07-24 18:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #20 from jv244 at cam dot ac dot uk  2010-07-24 18:12 -------
is this now fixed, all test cases seem to be passing ?


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
       [not found] <bug-38913-4@http.gcc.gnu.org/bugzilla/>
  2010-12-30 17:32 ` tkoenig at gcc dot gnu.org
@ 2011-07-24 18:47 ` dfranke at gcc dot gnu.org
  1 sibling, 0 replies; 23+ messages in thread
From: dfranke at gcc dot gnu.org @ 2011-07-24 18:47 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913

Daniel Franke <dfranke at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|WAITING                     |RESOLVED
                 CC|                            |dfranke at gcc dot gnu.org
         Resolution|                            |FIXED

--- Comment #22 from Daniel Franke <dfranke at gcc dot gnu.org> 2011-07-24 18:47:19 UTC ---
Closing according to comments #19 and #20.


^ permalink raw reply	[flat|nested] 23+ messages in thread

* [Bug fortran/38913] Fortran does not set TYPE_CANONICAL properly
       [not found] <bug-38913-4@http.gcc.gnu.org/bugzilla/>
@ 2010-12-30 17:32 ` tkoenig at gcc dot gnu.org
  2011-07-24 18:47 ` dfranke at gcc dot gnu.org
  1 sibling, 0 replies; 23+ messages in thread
From: tkoenig at gcc dot gnu.org @ 2010-12-30 17:32 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38913

Thomas Koenig <tkoenig at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |WAITING
                 CC|                            |tkoenig at gcc dot gnu.org

--- Comment #21 from Thomas Koenig <tkoenig at gcc dot gnu.org> 2010-12-30 17:31:51 UTC ---
Is this still an issue?


^ permalink raw reply	[flat|nested] 23+ messages in thread

end of thread, other threads:[~2011-07-24 18:47 UTC | newest]

Thread overview: 23+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-01-19 15:37 [Bug fortran/38913] New: Fortran does not set TYPE_CANONICAL properly rguenth at gcc dot gnu dot org
2009-01-19 16:23 ` [Bug fortran/38913] " rguenth at gcc dot gnu dot org
2009-01-21 20:22 ` pault at gcc dot gnu dot org
2009-01-21 20:50 ` rguenth at gcc dot gnu dot org
2009-01-25 15:25 ` dfranke at gcc dot gnu dot org
2009-02-06 13:45 ` pault at gcc dot gnu dot org
2009-02-07 15:33 ` jv244 at cam dot ac dot uk
2009-02-07 18:50 ` rguenther at suse dot de
2009-06-04 10:55 ` rguenth at gcc dot gnu dot org
2009-06-04 11:47 ` burnus at gcc dot gnu dot org
2009-06-04 11:49 ` rguenther at suse dot de
2009-06-04 12:52 ` burnus at gcc dot gnu dot org
2009-06-04 13:39 ` rguenther at suse dot de
2009-06-28 16:56 ` rguenth at gcc dot gnu dot org
2009-06-28 20:44 ` rguenth at gcc dot gnu dot org
2009-08-03 10:11 ` jv244 at cam dot ac dot uk
2009-09-22 15:45 ` rguenth at gcc dot gnu dot org
2009-10-11 12:49 ` jv244 at cam dot ac dot uk
2009-12-09 11:50 ` jv244 at cam dot ac dot uk
2010-06-09 22:11 ` fxcoudert at gcc dot gnu dot org
2010-07-24 18:12 ` jv244 at cam dot ac dot uk
     [not found] <bug-38913-4@http.gcc.gnu.org/bugzilla/>
2010-12-30 17:32 ` tkoenig at gcc dot gnu.org
2011-07-24 18:47 ` dfranke at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).