xref: /llvm-project/flang/test/Semantics/resolve103.f90 (revision d38765604f9372dab74a82b573302bd6401c6698)
1! RUN: not %flang_fc1 -pedantic %s 2>&1 | FileCheck %s
2! Test extension: allow forward references to dummy arguments or COMMON
3! from specification expressions in scopes with IMPLICIT NONE(TYPE),
4! as long as those symbols are eventually typed later with the
5! same integer type they would have had without IMPLICIT NONE.
6
7!CHECK: warning: 'n1' was used without (or before) being explicitly typed
8!CHECK: error: No explicit type declared for dummy argument 'n1'
9subroutine foo1(a, n1)
10  implicit none
11  real a(n1)
12end
13
14!CHECK: warning: 'n2' was used without (or before) being explicitly typed
15subroutine foo2(a, n2)
16  implicit none
17  real a(n2)
18!CHECK: error: The type of 'n2' has already been implicitly declared
19  double precision n2
20end
21
22!CHECK: warning: 'n3' was used without (or before) being explicitly typed
23!CHECK-NOT: error: Dummy argument 'n3'
24subroutine foo3(a, n3)
25  implicit none
26  real a(n3)
27  integer n3
28end
29
30!CHECK: warning: 'n4' was used without (or before) being explicitly typed
31!CHECK: error: No explicit type declared for 'n4'
32subroutine foo4(a)
33  implicit none
34  real a(n4)
35  common /b4/ n4
36end
37
38!CHECK: warning: 'n5' was used without (or before) being explicitly typed
39subroutine foo5(a)
40  implicit none
41  real a(n5)
42  common /b5/ n5
43!CHECK: error: The type of 'n5' has already been implicitly declared
44  double precision n5
45end
46
47!CHECK: warning: 'n6' was used without (or before) being explicitly typed
48subroutine foo6(a)
49  implicit none
50  real a(n6)
51  common /b6/ n6
52  integer n6
53end
54