URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [array_constructor_16.f90] - Rev 801
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do run }
! Tests the fix for PR31204, in which 'i' below would be incorrectly
! host associated by the contained subroutines. The checks for 'ii'
! and 'iii' have been added, since they can be host associated because
! of the explicit declarations in the main program.
!
! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
!
integer ii
INTEGER, PARAMETER :: jmin(1:10) = (/ (i, i = 1, 10) /)
INTEGER, PARAMETER :: kmin(1:10) = (/ (ii, ii = 1, 10) /)
INTEGER, PARAMETER :: lmin(1:10) = (/ (iii, iii = 1, 10) /)
integer iii
CALL two
CONTAINS
SUBROUTINE one
i = 99
ii = 99
iii = 999
END SUBROUTINE
SUBROUTINE two
i = 0
ii = 0
iii = 0
CALL one
IF (i .NE. 0) CALL ABORT ()
IF (ii .NE. 99) CALL ABORT ()
IF (iii .NE. 999) CALL ABORT ()
END SUBROUTINE
END
Go to most recent revision | Compare with Previous | Blame | View Log