This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[PATCH] Fix PR32921, alias pessimization with r126326


This fixes the mentioned PR by making sure not to re-set unbound array
types alias set to zero if it is used in two functions.

Bootstrapped and tested on x86_64-unknown-linux-gnu, applied to mainline.

Richard.

2007-10-19  Richard Guenther  <rguenther@suse.de>

	PR middle-end/32921
	* tree.c (build_array_type): Do not re-layout unbound array
	types.

	* gfortran.dg/pr32921.f: New testcase.

Index: tree.c
===================================================================
*** tree.c	(revision 129439)
--- tree.c	(working copy)
*************** build_array_type (tree elt_type, tree in
*** 5665,5671 ****
    hashcode = iterative_hash_object (TYPE_HASH (index_type), hashcode);
    t = type_hash_canon (hashcode, t);
  
!   if (!COMPLETE_TYPE_P (t))
      layout_type (t);
  
    if (TYPE_CANONICAL (t) == t)
--- 5665,5671 ----
    hashcode = iterative_hash_object (TYPE_HASH (index_type), hashcode);
    t = type_hash_canon (hashcode, t);
  
!   if (!COMPLETE_OR_UNBOUND_ARRAY_TYPE_P (t))
      layout_type (t);
  
    if (TYPE_CANONICAL (t) == t)
Index: testsuite/gfortran.dg/pr32921.f
===================================================================
*** testsuite/gfortran.dg/pr32921.f	(revision 0)
--- testsuite/gfortran.dg/pr32921.f	(revision 0)
***************
*** 0 ****
--- 1,49 ----
+ ! { dg-do compile }
+ ! { dg-options "-O2 -fdump-tree-lim" }
+ ! gfortran -c -m32 -O2 -S junk.f
+ !
+       MODULE LES3D_DATA
+ 
+       IMPLICIT REAL*8 (A-H,O-Z)
+ 
+       PARAMETER ( NSPECI = 1, ND = 7 + NSPECI )
+ 
+       INTEGER IMAX
+ 
+       DOUBLE PRECISION,ALLOCATABLE,DIMENSION(:,:,:) ::
+      >         UAV,QAV
+ 
+ 
+       END MODULE LES3D_DATA
+ !---------------------------------------------------------------------
+ !------------------------------------------------------------------------
+       SUBROUTINE FLUXI()
+ 
+       USE LES3D_DATA
+       IMPLICIT REAL*8(A-H,O-Z)
+ 
+       ALLOCATABLE QS(:)
+ 
+       ALLOCATE( QS(0:IMAX))
+       QS=0D0
+ 
+       RETURN
+       END
+ !------------------------------------------------------------------------
+ !------------------------------------------------------------------------
+       SUBROUTINE EXTRAPI()
+ 
+       USE LES3D_DATA
+       IMPLICIT REAL*8(A-H,O-Z)
+ 
+       I1 = 0
+       I2 = IMAX - 1
+ 
+             DO I = I1, I2
+                UAV(I,1,2) = QAV(I,1,2)
+             END DO
+ 
+       RETURN
+       END
+ ! { dg-final { scan-tree-dump-times "stride" 6 "lim" } }
+ ! { dg-final { cleanup-tree-dump "lim" } }


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]