OSDN Git Service

PR target/35944
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / host_assoc_call_1.f90
1 ! { dg-do compile }
2 ! Tests the fix for PR31494, where the call of sub2 would reference
3 ! the variable, rather than the contained subroutine.
4 !
5 ! Contributed by Michael Richmond <michael.a.richmond@nasa.gov>
6 !
7 MODULE ksbin2_aux_mod
8 REAL, DIMENSION(1) :: sub2
9 CONTAINS
10   SUBROUTINE sub1
11     CALL sub2
12     CONTAINS 
13       SUBROUTINE sub2
14       END SUBROUTINE sub2
15   END SUBROUTINE sub1
16 END MODULE ksbin2_aux_mod
17 ! { dg-final { cleanup-modules "ksbin2_aux_mod" } }