xref: /llvm-project/flang/test/Semantics/resolve17.f90 (revision 2236048f5fdde70dd95e97ccc87437424a371cef)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2module m
3  integer :: foo
4  !Note: PGI, Intel, and GNU allow this; NAG and Sun do not
5  !ERROR: 'foo' is already declared in this scoping unit
6  interface foo
7  end interface
8end module
9
10module m2
11  interface s
12  end interface
13contains
14  !WARNING: 's' should not be the name of both a generic interface and a procedure unless it is a specific procedure of the generic
15  subroutine s
16  end subroutine
17end module
18
19module m3
20  ! This is okay: s is generic and specific
21  interface s
22    procedure s2
23  end interface
24  interface s
25    procedure s
26  end interface
27contains
28  subroutine s()
29  end subroutine
30  subroutine s2(x)
31  end subroutine
32end module
33
34module m4a
35  interface g
36    procedure s_real
37  end interface
38contains
39  subroutine s_real(x)
40  end
41end
42module m4b
43  interface g
44    procedure s_int
45  end interface
46contains
47  subroutine s_int(i)
48  end
49end
50! Generic g should merge the two use-associated ones
51subroutine s4
52  use m4a
53  use m4b
54  call g(123)
55  call g(1.2)
56end
57
58module m5a
59  interface g
60    procedure s_real
61  end interface
62contains
63  subroutine s_real(x)
64  end
65end
66module m5b
67  interface gg
68    procedure s_int
69  end interface
70contains
71  subroutine s_int(i)
72  end
73end
74! Generic g should merge the two use-associated ones
75subroutine s5
76  use m5a
77  use m5b, g => gg
78  call g(123)
79  call g(1.2)
80end
81
82module m6a
83  interface gg
84    procedure sa
85  end interface
86contains
87  subroutine sa(x)
88  end
89end
90module m6b
91  interface gg
92    procedure sb
93  end interface
94contains
95  subroutine sb(y)
96  end
97end
98subroutine s6
99  !ERROR: Generic 'g' may not have specific procedures 'sa' and 'sb' as their interfaces are not distinguishable
100  use m6a, g => gg
101  use m6b, g => gg
102end
103
104module m7a
105  interface g
106    procedure s1
107  end interface
108contains
109  subroutine s1(x)
110  end
111end
112module m7b
113  interface g
114    procedure s2
115  end interface
116contains
117  subroutine s2(x, y)
118  end
119end
120module m7c
121  interface g
122    procedure s3
123  end interface
124contains
125  subroutine s3(x, y, z)
126  end
127end
128! Merge the three use-associated generics
129subroutine s7
130  use m7a
131  use m7b
132  use m7c
133  call g(1.0)
134  call g(1.0, 2.0)
135  call g(1.0, 2.0, 3.0)
136end
137
138module m8a
139  interface g
140    procedure s1
141  end interface
142contains
143  subroutine s1(x)
144  end
145end
146module m8b
147  interface g
148    procedure s2
149  end interface
150contains
151  subroutine s2(x, y)
152  end
153end
154module m8c
155  integer :: g
156end
157! If merged generic conflicts with another USE, it is an error (if it is referenced)
158subroutine s8
159  use m8a
160  use m8b
161  use m8c
162  !ERROR: Reference to 'g' is ambiguous
163  g = 1
164end
165
166module m9a
167  interface g
168    module procedure g
169  end interface
170contains
171  subroutine g()
172  end
173end module
174module m9b
175  interface g
176    module procedure g
177  end interface
178contains
179  subroutine g()
180  end
181end module
182subroutine s9
183  !PORTABILITY: USE-associated generic 'g' should not have specific procedures 'g' and 'g' as their interfaces are not distinguishable
184  use m9a
185  use m9b
186end
187
188module m10a
189  interface g
190    module procedure s
191  end interface
192  private :: s
193contains
194  subroutine s(x)
195    integer :: x
196  end
197end
198module m10b
199  use m10a
200  !ERROR: Generic 'g' may not have specific procedures 's' and 's' as their interfaces are not distinguishable
201  interface g
202    module procedure s
203  end interface
204  private :: s
205contains
206  subroutine s(x)
207    integer :: x
208  end
209end
210
211module m12a
212  interface ga
213    module procedure sa
214  end interface
215contains
216  subroutine sa(i)
217  end
218end
219module m12b
220  use m12a
221  interface gb
222    module procedure sb
223  end interface
224contains
225  subroutine sb(x)
226  end
227end
228module m12c
229  use m12b, only: gc => gb
230end
231module m12d
232  use m12a, only: g => ga
233  use m12c, only: g => gc
234  interface g
235  end interface
236end module
237
238module m13a
239 contains
240  subroutine subr
241  end subroutine
242end module
243module m13b
244  use m13a
245  interface subr
246    module procedure subr
247  end interface
248end module
249module m13c
250  use m13a
251  use m13b
252 contains
253  subroutine test
254    call subr
255  end subroutine
256end module
257module m13d
258  use m13b
259  use m13a
260 contains
261  subroutine test
262    call subr
263  end subroutine
264end module
265
266module m14a
267  type :: foo
268    integer :: n
269  end type
270end module
271module m14b
272  interface foo
273    module procedure bar
274  end interface
275 contains
276  real function bar(x)
277    real, intent(in) :: x
278    bar = x
279  end function
280end module
281module m14c
282  use m14a
283  use m14b
284  type(foo) :: x
285end module
286module m14d
287  use m14a
288  use m14b
289  type(foo) :: x
290 contains
291  subroutine test
292    real :: y
293    y = foo(1.0)
294    x = foo(2)
295  end subroutine
296end module
297module m14e
298  use m14b
299  use m14a
300  type(foo) :: x
301 contains
302  subroutine test
303    real :: y
304    y = foo(1.0)
305    x = foo(2)
306  end subroutine
307end module
308
309module m15a
310  interface foo
311    module procedure bar
312  end interface
313 contains
314  subroutine bar
315  end subroutine
316end module
317module m15b
318  !ERROR: Cannot use-associate 'foo'; it is already declared in this scope
319  use m15a
320 contains
321  subroutine foo
322  end subroutine
323end module
324module m15c
325 contains
326  subroutine foo
327  end subroutine
328end module
329module m15d
330  use m15a
331  use m15c
332 contains
333  subroutine test
334    !ERROR: Reference to 'foo' is ambiguous
335    call foo
336  end subroutine
337end module
338