PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / associated_5.f90
blobd70e5f5a18e2fcb868998e3673cfc4eea433c5af
1 ! { dg-do run }
2 ! PR 35719 - associated used to fail with zero-sized automatic arrays
3 ! Test case contributed by Dick Hendrickson
5 program try_mf1053
7 call mf1053 ( 1, 2, 3, 4)
8 end
10 SUBROUTINE MF1053 (nf1, nf2, nf3, nf4)
11 INTEGER, pointer :: ptr(:,:)
12 INTEGER, target :: ILA1(NF2,NF4:NF3)
14 ptr => ILA1
16 if (ASSOCIATED (ptr, ILA1(NF1:NF2,NF4:NF3) ) ) STOP 1
17 if ( .not. ASSOCIATED(ptr) ) STOP 2
19 END SUBROUTINE