arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / implicit_16.f90
blobb44be6708fa847b64307aa9dfe0c7a94360f3b6a
1 ! { dg-do compile }
2 ! { dg-options "" }
4 ! Support Fortran 2015's IMPLICIT NONE with empty spec list
6 ! And IMPLICIT with ";" followed by an additional statement.
7 ! Contributed by Alan Greynolds
10 module m
11 type t
12 end type t
13 end module m
15 subroutine sub0
16 implicit integer (a-h,o-z); parameter (i=0)
17 end subroutine sub0
19 subroutine sub1
20 implicit integer (a-h,o-z)!test
21 parameter (i=0)
22 end subroutine sub1
24 subroutine sub2
25 use m
26 implicit type(t) (a-h,o-z); parameter (i=0)
27 end subroutine sub2
30 subroutine sub3
31 use m
32 implicit type(t) (a-h,o-z)! Foobar
33 parameter (i=0)
34 end subroutine sub3
36 subroutine sub4
37 implicit none ()
38 call test()
39 i = 1 ! { dg-error "Symbol 'i' at .1. has no IMPLICIT type" }
40 end subroutine sub4