xref: /llvm-project/flang/test/Semantics/resolve09.f90 (revision ea2c88f51297eb0ef8d352d650bb71b0292d9898)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2integer :: y
3procedure() :: a
4procedure(real) :: b
5call a  ! OK - can be function or subroutine
6!ERROR: Cannot call subroutine 'a' like a function
7c = a()
8!ERROR: Cannot call function 'b' like a subroutine
9call b
10!ERROR: Cannot call function 'y' like a subroutine
11call y
12call x
13!ERROR: Cannot call subroutine 'x' like a function
14z = x()
15end
16
17subroutine s
18  !ERROR: Cannot call function 'f' like a subroutine
19  call f
20  !ERROR: Cannot call subroutine 's' like a function
21  i = s()
22contains
23  function f()
24  end
25end
26
27subroutine s2
28  ! subroutine vs. function is determined by use
29  external :: a, b
30  call a()
31  !ERROR: Cannot call subroutine 'a' like a function
32  x = a()
33  x = b()
34  !ERROR: Cannot call function 'b' like a subroutine
35  call b()
36end
37
38subroutine s3
39  ! subroutine vs. function is determined by use, even in internal subprograms
40  external :: a
41  procedure() :: b
42contains
43  subroutine s3a()
44    x = a()
45    call b()
46  end
47  subroutine s3b()
48    !ERROR: Cannot call function 'a' like a subroutine
49    call a()
50    !ERROR: Cannot call subroutine 'b' like a function
51    x = b()
52  end
53end
54
55module m1
56  !Function vs subroutine in a module is resolved to a subroutine if
57  !no other information.
58  external :: exts, extf, extunk
59  procedure() :: procs, procf, procunk
60contains
61  subroutine s
62    call exts()
63    call procs()
64    x = extf()
65    x = procf()
66  end
67end
68
69module m2
70  use m1
71 contains
72  subroutine test
73    call exts() ! ok
74    call procs() ! ok
75    call extunk() ! ok
76    call procunk() ! ok
77    x = extf() ! ok
78    x = procf() ! ok
79    !ERROR: Cannot call subroutine 'extunk' like a function
80    !ERROR: Function result characteristics are not known
81    x = extunk()
82    !ERROR: Cannot call subroutine 'procunk' like a function
83    !ERROR: Function result characteristics are not known
84    x = procunk()
85  end
86end
87
88module modulename
89end
90
91! Call to entity in global scope, even with IMPORT, NONE
92subroutine s4
93  block
94    import, none
95    integer :: i
96    !ERROR: 'modulename' is not a callable procedure
97    call modulename()
98  end block
99end
100
101! Call to entity in global scope, even with IMPORT, NONE
102subroutine s5
103  block
104    import, none
105    integer :: i
106    i = foo()
107    !ERROR: Cannot call function 'foo' like a subroutine
108    call foo()
109  end block
110end
111
112subroutine s6
113  call a6()
114end
115!ERROR: 'a6' was previously called as a subroutine
116function a6()
117  a6 = 0.0
118end
119
120subroutine s7
121  x = a7()
122end
123!ERROR: 'a7' was previously called as a function
124subroutine a7()
125end
126
127!OK: use of a8 and b8 is consistent
128subroutine s8
129  call a8()
130  x = b8()
131end
132subroutine a8()
133end
134function b8()
135  b8 = 0.0
136end
137
138subroutine s9
139  type t
140    procedure(), nopass, pointer :: p1, p2
141  end type
142  type(t) x
143  print *, x%p1()
144  call x%p2
145  !ERROR: Cannot call function 'p1' like a subroutine
146  call x%p1
147  !ERROR: Cannot call subroutine 'p2' like a function
148  print *, x%p2()
149end subroutine
150
151subroutine s10
152  call a10
153  !ERROR: Actual argument for 'a=' may not be a procedure
154  print *, abs(a10)
155end
156
157subroutine s11
158  real, pointer :: p(:)
159  !ERROR: A NULL() pointer is not allowed for 'a=' intrinsic argument
160  print *, rank(null())
161  print *, rank(null(mold=p)) ! ok
162end
163