https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64247

--- Comment #9 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 
---
A variation on the testcase, to indicate how this behavior leads to conflicts
with the Fortran language standard. A routine declared 'PURE' and called with
all intent(in) arguments having the same value, returns different results.

> gfortran -g -mavx -O3 -ffast-math test.f90 && echo 8 | ./a.out
 pure routine gives different results at iter:            1
 pure routine gives different results at iter:            3
 pure routine gives different results at iter:            5
 pure routine gives different results at iter:            7
 pure routine gives different results at iter:            9

> cat test.f90
MODULE M1
CONTAINS
  PURE SUBROUTINE gemm(C,A,B,N)
   INTEGER, INTENT(IN) :: N
   REAL*8, INTENT(IN)  :: A(N,N), B(N,N)
   REAL*8, INTENT(OUT) :: C(N,N)
   C=0
   DO i=1,N
    DO j=1,N
     DO k=1,N     
      C(i,j)=C(i,j)+A(k,i)*B(k,j)
     ENDDO
    ENDDO
   ENDDO
  END SUBROUTINE gemm
END MODULE

PROGRAM TEST
USE M1
REAL*8, DIMENSION(:,:), POINTER, CONTIGUOUS :: A1,B1,C1
REAL*8, DIMENSION(:,:), POINTER, CONTIGUOUS :: A2,B2,C2
INTEGER :: N
READ(5,*) N
ALLOCATE(A1(N,N),B1(N,N),C1(N,N))
CALL RANDOM_NUMBER(A1)
CALL RANDOM_NUMBER(B1)
CALL GEMM(C1,A1,B1,N)

DO I=1,10
  ALLOCATE(A2(N,N),B2(N,N),C2(N,N))
  A2=A1 ; B2=B1
  CALL GEMM(C2,A2,B2,N)
  IF (ANY(C1.NE.C2)) THEN
     WRITE(6,*) "pure routine gives different results at iter: ",i
  ENDIF
ENDDO

END PROGRAM TEST

Reply via email to