------- Comment #3 from dominiq at lps dot ens dot fr  2007-03-11 12:58 -------
The following reduced test case

      PROGRAM LINPK
      PARAMETER (N=2500,LDA=N+1)
      DOUBLE PRECISION a(LDA,N) , b(N) , x(N)

      a = 1.0
      print *, 'before DSCAL'
      CALL DSCAL(N-1,1.0D0,A(2,1),1)
      print *, 'after DSCAL'

      END

      SUBROUTINE DSCAL(N,Da,Dx,Incx)
      DOUBLE PRECISION Da , Dx(*)
      INTEGER i , Incx , m , mp1 , N , nincx

!      print *, N, Da, Dx(MOD(N,5)+1), Incx
      IF ( N.GT.0 ) THEN
            mp1 = MOD(N,5) + 1
            DO i = mp1 , N , 5
               Dx(i) = Da*Dx(i)
            ENDDO
      ENDIF
      END

shows the bug:

[karma] lin/source% gfc -O2 linpk_red.f90
[karma] lin/source% a.out 
 before DSCAL
Bus error

Looking at linpk_red.f90.116t.optimized, the loop in DSCAL reads

<L2>:;
  D.1053 = (<unnamed type>) ivtmp.54;
  MEM[index: D.1053] = pretmp.36 * MEM[index: D.1053];
  ivtmp.45 = ivtmp.45 + 1;
  ivtmp.54 = ivtmp.54 + 40;
  if (ivtmp.45 == 2147483647) goto L.4; else goto <L2>;

I don't know the origin of 2147483647, but it looks pretty bad!-(even for me)

Note that DSCAL appears in linpk.f90, rnflow.f90, and test_fpu.f90.

PS this is my second attempt to post this, I apologize if the first one shows
up later.


-- 


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

Reply via email to