URL
https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk
Subversion Repositories openrisc_2011-10-31
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [associated_5.f90] - Rev 399
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do run }
! PR 35719 - associated used to fail with zero-sized automatic arrays
! Test case contributed by Dick Hendrickson
program try_mf1053
call mf1053 ( 1, 2, 3, 4)
end
SUBROUTINE MF1053 (nf1, nf2, nf3, nf4)
INTEGER, pointer :: ptr(:,:)
INTEGER, target :: ILA1(NF2,NF4:NF3)
ptr => ILA1
if (ASSOCIATED (ptr, ILA1(NF1:NF2,NF4:NF3) ) ) call abort
if ( .not. ASSOCIATED(ptr) ) call abort
END SUBROUTINE
Go to most recent revision | Compare with Previous | Blame | View Log