AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / external_implicit_none_2.f90
blobb2b1dd1e6d79989f0356049c06fa1f2a05b49f48
1 ! { dg-do compile }
3 ! PR fortran/93309
5 module m
6 implicit none(external)
7 contains
8 subroutine s
9 implicit none(external) ! OK
10 end subroutine
11 end module
13 module m2
14 implicit none(external)
15 contains
16 subroutine s
17 call foo(1) ! { dg-error "not explicitly declared" }
18 end subroutine
19 end module
21 module m3
22 implicit none(external)
23 contains
24 subroutine s
25 implicit none(external) ! OK
26 implicit none(external) ! { dg-error "Duplicate IMPLICIT NONE statement" }
27 end subroutine
28 end module