]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
revert: re PR tree-optimization/32921 (Revision 126326 causes 12% slowdown)
authorRichard Guenther <rguenther@suse.de>
Fri, 19 Oct 2007 12:27:25 +0000 (12:27 +0000)
committerRichard Biener <rguenth@gcc.gnu.org>
Fri, 19 Oct 2007 12:27:25 +0000 (12:27 +0000)
2007-10-19  Richard Guenther  <rguenther@suse.de>

        Revert
        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.

From-SVN: r129487

gcc/ChangeLog
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/pr32921.f [deleted file]
gcc/tree.c

index 5756ae8e61e30ef2763e2c5146d1ff7211616816..14f14ccf71105cd6747d48b826ad0072e797857f 100644 (file)
@@ -1,3 +1,12 @@
+2007-10-19  Richard Guenther  <rguenther@suse.de>
+
+       Revert
+       2007-10-19  Richard Guenther  <rguenther@suse.de>
+
+       PR middle-end/32921
+       * tree.c (build_array_type): Do not re-layout unbound array
+       types.
+
 2007-10-19  Richard Guenther  <rguenther@suse.de>
 
        PR middle-end/32921
index fb172cd9239392a07276babe9391a1c674c761a0..acd2bb6ddfdc8171356bad362875d60f650b763b 100644 (file)
@@ -1,3 +1,11 @@
+2007-10-19  Richard Guenther  <rguenther@suse.de>
+
+       Revert
+       2007-10-19  Richard Guenther  <rguenther@suse.de>
+
+       PR middle-end/32921
+       * gfortran.dg/pr32921.f: New testcase.
+
 2007-10-19  Richard Guenther  <rguenther@suse.de>
 
        * gcc.c-torture/execute/20071018-1.c: New testcase.
diff --git a/gcc/testsuite/gfortran.dg/pr32921.f b/gcc/testsuite/gfortran.dg/pr32921.f
deleted file mode 100644 (file)
index d110301..0000000
+++ /dev/null
@@ -1,49 +0,0 @@
-! { 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 3cfa55d911bee95e794cee504d2d0297066824b6..88ec29e13e37d287c0574efcd0d8e49e366dbbef 100644 (file)
@@ -5665,7 +5665,7 @@ build_array_type (tree elt_type, tree index_type)
   hashcode = iterative_hash_object (TYPE_HASH (index_type), hashcode);
   t = type_hash_canon (hashcode, t);
 
-  if (!COMPLETE_OR_UNBOUND_ARRAY_TYPE_P (t))
+  if (!COMPLETE_TYPE_P (t))
     layout_type (t);
 
   if (TYPE_CANONICAL (t) == t)