revert: re PR tree-optimization/32921 (Revision 126326 causes 12% slowdown)

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
This commit is contained in:
Richard Guenther 2007-10-19 12:27:25 +00:00 committed by Richard Biener
parent 6525c3f01e
commit ab58d043a7
4 changed files with 18 additions and 50 deletions

View 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

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

View File

@ -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" } }

View 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)