nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / implicit_15.f90
blob02a5fefbda66d374c5c7c50c7f8754b3ab886f5a
1 ! { dg-do compile }
2 ! { dg-options "" }
4 ! Support Fortran 2015's IMPLICIT NONE with spec list
7 subroutine sub1
8 implicit none (type)
9 call test()
10 i = 1 ! { dg-error "Symbol 'i' at .1. has no IMPLICIT type" }
11 end subroutine sub1
13 subroutine sub2
14 implicit none ( external )
15 call foo() ! { dg-error "Procedure 'foo' called at .1. is not explicitly declared" }
16 i = 2
17 end subroutine sub2
19 subroutine sub3
20 implicit none ( external, type, external, type )
21 call foo() ! { dg-error "Procedure 'foo' called at .1. is not explicitly declared" }
22 i = 3 ! { dg-error "Symbol 'i' at .1. has no IMPLICIT type" }
23 end subroutine sub3
25 subroutine sub4
26 implicit none ( external ,type)
27 external foo
28 call foo()
29 i = 4 ! { dg-error "Symbol 'i' at .1. has no IMPLICIT type" }
30 end subroutine sub4
32 subroutine sub5 ! OK
33 implicit integer(a-z)
34 implicit none ( external )
35 procedure() :: foo
36 call foo()
37 i = 5
38 end subroutine sub5
40 subroutine sub6 ! OK
41 implicit none ( external )
42 implicit integer(a-z)
43 procedure() :: foo
44 call foo()
45 i = 5
46 end subroutine sub6
48 subroutine sub7
49 implicit none ( external )
50 implicit none ! { dg-error "Duplicate IMPLICIT NONE statement" }
51 end subroutine sub7
53 subroutine sub8
54 implicit none
55 implicit none ( type ) ! { dg-error "Duplicate IMPLICIT NONE statement" }
56 end subroutine sub8
58 subroutine sub9
59 implicit none ( external, type )
60 implicit integer(a-z) ! { dg-error "IMPLICIT statement at .1. following an IMPLICIT NONE .type. statement" }
61 procedure() :: foo
62 call foo()
63 end subroutine sub9
65 subroutine sub10
66 implicit integer(a-z)
67 implicit none ( external, type ) ! { dg-error "IMPLICIT NONE .type. statement at .1. following an IMPLICIT statement" }
68 procedure() :: foo
69 call foo()
70 end subroutine sub10