This is the mail archive of the gcc-bugs@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]

[Bug tree-optimization/52275] The polyhedron test air.f90 is miscompiled with '-O2 -floop-flatten' after revision 184265


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

--- Comment #4 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2012-02-16 14:19:30 UTC ---
This is the following subroutine that is miscompiled at '-O2 -floop-flatten':

!*==SPECTOP.spg  processed by SPAG 6.55Dc at 09:26 on 23 Sep 2005
!
! other routines
!
      SUBROUTINE SPECTOP(Dr,N)
      IMPLICIT REAL*8(A-H,o-Z)
      DIMENSION d1(0:32,0:32) , Dr(0:32,0:32) , x(0:32)
      REAL*8 Dr
!
! PROGRAM TO COMPUTE THE CHEBYSHEV SPECTRAL OPERATOR
!
      ang = DBLE(1)
      s = DBLE(6)
      o = DBLE(1)
      t = DBLE(2)
      pi = t*DASIN(ang)
      DO i = 0 , N
         x(i) = DCOS(pi*DBLE(i)/DBLE(N))
      ENDDO
!
! IF J=K
!
      DO j = 1 , N - 1
         d1(j,j) = -x(j)/(t*(o-x(j)**2))
      ENDDO
      d1(0,0) = (t*DBLE(N)**2+o)/s
      d1(N,N) = -d1(0,0)
!
! IF J.NE.K
!
      fctr1 = 1.0D0
      DO k = 0 , N
         ck = 1.0D0
         IF ( k.EQ.0 ) ck = t
         IF ( k.EQ.N ) ck = t
         fctr2 = o
         DO j = 0 , N
            cj = o
            IF ( j.EQ.0 ) cj = t
            IF ( j.EQ.N ) cj = t
            fctr = fctr1*fctr2
            IF ( j.NE.k ) THEN
               d1(k,j) = ck*fctr/(cj*(x(k)-x(j)))
            ENDIF
            fctr2 = -o*fctr2
         ENDDO
         fctr1 = -o*fctr1
      ENDDO
      DO k = 0 , N
         DO j = 0 , N
            Dr(k,j) = d1(N-k,N-j)
         ENDDO
      ENDDO
      CONTINUE
      END


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