OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [pr29581.f90] - Rev 823

Go to most recent revision | Compare with Previous | Blame | View Log

! PR tree-optimization/29581
! { dg-do run }
! { dg-options "-O2 -ftree-loop-linear" }

      SUBROUTINE FOO (K)
      INTEGER I, J, K, A(5,5), B
      COMMON A
      A(1,1) = 1
 10   B = 0
      DO 30 I = 1, K
        DO 20 J = 1, K
          B = B + A(I,J)
 20     CONTINUE
        A(I,I) = A(I,I) * 2
 30   CONTINUE
      IF (B.GE.3) RETURN
      GO TO 10
      END SUBROUTINE

      PROGRAM BAR
        INTEGER A(5,5)
        COMMON A
        CALL FOO (2)
        IF (A(1,1).NE.8) CALL ABORT
        A(1,1) = 0
        IF (ANY(A.NE.0)) CALL ABORT
      END

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.