Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / modfile07.f90
blob48df7243e308c75f84f143eccc2a220cb93fc75e
1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Check modfile generation for generic interfaces
3 module m1
4 interface foo
5 real function s1(x,y)
6 real, intent(in) :: x
7 logical, intent(in) :: y
8 end function
9 complex function s2(x,y)
10 complex, intent(in) :: x
11 logical, intent(in) :: y
12 end function
13 end interface
14 generic :: operator ( + ) => s1, s2
15 interface operator ( /= )
16 logical function f1(x, y)
17 real, intent(in) :: x
18 logical, intent(in) :: y
19 end function
20 end interface
21 interface
22 logical function f2(x, y)
23 complex, intent(in) :: x
24 logical, intent(in) :: y
25 end function
26 logical function f3(x, y)
27 integer, intent(in) :: x
28 logical, intent(in) :: y
29 end function
30 end interface
31 generic :: operator(.ne.) => f2
32 generic :: operator(<>) => f3
33 private :: operator( .ne. )
34 interface bar
35 procedure :: s1
36 procedure :: s2
37 procedure :: s3
38 procedure :: s4
39 end interface
40 interface operator( .bar.)
41 procedure :: s1
42 procedure :: s2
43 procedure :: s3
44 procedure :: s4
45 end interface
46 contains
47 logical function s3(x,y)
48 logical, intent(in) :: x,y
49 end function
50 integer function s4(x,y)
51 integer, intent(in) :: x,y
52 end function
53 end
54 !Expect: m1.mod
55 !module m1
56 ! interface foo
57 ! procedure::s1
58 ! procedure::s2
59 ! end interface
60 ! interface
61 ! function s1(x,y)
62 ! real(4),intent(in)::x
63 ! logical(4),intent(in)::y
64 ! real(4)::s1
65 ! end
66 ! end interface
67 ! interface
68 ! function s2(x,y)
69 ! complex(4),intent(in)::x
70 ! logical(4),intent(in)::y
71 ! complex(4)::s2
72 ! end
73 ! end interface
74 ! interface operator(+)
75 ! procedure::s1
76 ! procedure::s2
77 ! end interface
78 ! interface operator(/=)
79 ! procedure::f1
80 ! procedure::f2
81 ! procedure::f3
82 ! end interface
83 ! private::operator(/=)
84 ! interface
85 ! function f1(x,y)
86 ! real(4),intent(in)::x
87 ! logical(4),intent(in)::y
88 ! logical(4)::f1
89 ! end
90 ! end interface
91 ! interface
92 ! function f2(x,y)
93 ! complex(4),intent(in)::x
94 ! logical(4),intent(in)::y
95 ! logical(4)::f2
96 ! end
97 ! end interface
98 ! interface
99 ! function f3(x,y)
100 ! integer(4),intent(in)::x
101 ! logical(4),intent(in)::y
102 ! logical(4)::f3
103 ! end
104 ! end interface
105 ! interface bar
106 ! procedure::s1
107 ! procedure::s2
108 ! procedure::s3
109 ! procedure::s4
110 ! end interface
111 ! interface operator(.bar.)
112 ! procedure::s1
113 ! procedure::s2
114 ! procedure::s3
115 ! procedure::s4
116 ! end interface
117 !contains
118 ! function s3(x,y)
119 ! logical(4),intent(in)::x
120 ! logical(4),intent(in)::y
121 ! logical(4)::s3
122 ! end
123 ! function s4(x,y)
124 ! integer(4),intent(in)::x
125 ! integer(4),intent(in)::y
126 ! integer(4)::s4
127 ! end
128 !end
130 module m1b
131 use m1
133 !Expect: m1b.mod
134 !module m1b
135 ! use m1,only:foo
136 ! use m1,only:s1
137 ! use m1,only:s2
138 ! use m1,only:operator(+)
139 ! use m1,only:f1
140 ! use m1,only:f2
141 ! use m1,only:f3
142 ! use m1,only:bar
143 ! use m1,only:operator(.bar.)
144 ! use m1,only:s3
145 ! use m1,only:s4
146 !end
148 module m1c
149 use m1, only: myfoo => foo
150 use m1, only: operator(.bar.)
151 use m1, only: operator(.mybar.) => operator(.bar.)
152 use m1, only: operator(+)
154 !Expect: m1c.mod
155 !module m1c
156 ! use m1,only:myfoo=>foo
157 ! use m1,only:operator(.bar.)
158 ! use m1,only:operator(.mybar.)=>operator(.bar.)
159 ! use m1,only:operator(+)
160 !end
162 module m2
163 interface foo
164 procedure foo
165 end interface
166 contains
167 complex function foo()
168 foo = 1.0
171 !Expect: m2.mod
172 !module m2
173 ! interface foo
174 ! procedure::foo
175 ! end interface
176 !contains
177 ! function foo()
178 ! complex(4)::foo
179 ! end
180 !end
182 module m2b
183 type :: foo
184 real :: x
185 end type
186 interface foo
187 end interface
188 private :: bar
189 interface bar
190 end interface
192 !Expect: m2b.mod
193 !module m2b
194 ! interface foo
195 ! end interface
196 ! type::foo
197 ! real(4)::x
198 ! end type
199 ! interface bar
200 ! end interface
201 ! private::bar
202 !end
204 ! Test interface nested inside another interface
205 module m3
206 interface g
207 subroutine s1(f)
208 interface
209 real function f(x)
210 interface
211 subroutine x()
212 end subroutine
213 end interface
214 end function
215 end interface
216 end subroutine
217 end interface
219 !Expect: m3.mod
220 !module m3
221 ! interface g
222 ! procedure::s1
223 ! end interface
224 ! interface
225 ! subroutine s1(f)
226 ! interface
227 ! function f(x)
228 ! interface
229 ! subroutine x()
230 ! end
231 ! end interface
232 ! real(4)::f
233 ! end
234 ! end interface
235 ! end
236 ! end interface
237 !end
239 module m4
240 interface foo
241 integer function foo()
242 end function
243 integer function f(x)
244 end function
245 end interface
247 subroutine s4
248 use m4
249 i = foo()
251 !Expect: m4.mod
252 !module m4
253 ! interface foo
254 ! procedure::foo
255 ! procedure::f
256 ! end interface
257 ! interface
258 ! function foo()
259 ! integer(4)::foo
260 ! end
261 ! end interface
262 ! interface
263 ! function f(x)
264 ! real(4)::x
265 ! integer(4)::f
266 ! end
267 ! end interface
268 !end
270 ! Compile contents of m4.mod and verify it gets the same thing again.
271 module m5
272 interface foo
273 procedure::foo
274 procedure::f
275 end interface
276 interface
277 function foo()
278 integer(4)::foo
280 end interface
281 interface
282 function f(x)
283 integer(4)::f
284 real(4)::x
286 end interface
288 !Expect: m5.mod
289 !module m5
290 ! interface foo
291 ! procedure::foo
292 ! procedure::f
293 ! end interface
294 ! interface
295 ! function foo()
296 ! integer(4)::foo
297 ! end
298 ! end interface
299 ! interface
300 ! function f(x)
301 ! real(4)::x
302 ! integer(4)::f
303 ! end
304 ! end interface
305 !end
307 module m6a
308 interface operator(<)
309 logical function lt(x, y)
310 logical, intent(in) :: x, y
311 end function
312 end interface
314 !Expect: m6a.mod
315 !module m6a
316 ! interface operator(<)
317 ! procedure::lt
318 ! end interface
319 ! interface
320 ! function lt(x,y)
321 ! logical(4),intent(in)::x
322 ! logical(4),intent(in)::y
323 ! logical(4)::lt
324 ! end
325 ! end interface
326 !end
328 module m6b
329 use m6a, only: operator(.lt.)
331 !Expect: m6b.mod
332 !module m6b
333 ! use m6a,only:operator(.lt.)
334 !end
336 module m7a
337 interface g_integer
338 module procedure s
339 end interface
340 private :: s
341 contains
342 subroutine s(x)
343 integer :: x
346 !Expect: m7a.mod
347 !module m7a
348 ! interface g_integer
349 ! procedure :: s
350 ! end interface
351 ! private :: s
352 !contains
353 ! subroutine s(x)
354 ! integer(4) :: x
355 ! end
356 !end
358 module m7b
359 interface g_real
360 module procedure s
361 end interface
362 private :: s
363 contains
364 subroutine s(x)
365 real :: x
366 end subroutine
368 !Expect: m7b.mod
369 !module m7b
370 ! interface g_real
371 ! procedure :: s
372 ! end interface
373 ! private :: s
374 !contains
375 ! subroutine s(x)
376 ! real(4) :: x
377 ! end
378 !end
380 module m7c
381 use m7a, only: g => g_integer
382 use m7b, only: g => g_real
383 interface g
384 module procedure s
385 end interface
386 private :: s
387 contains
388 subroutine s(x)
389 complex :: x
390 end subroutine
391 subroutine test()
392 real :: x
393 integer :: y
394 complex :: z
395 call g(x)
396 call g(y)
397 call g(z)
400 !Expect: m7c.mod
401 !module m7c
402 ! use m7a, only: g => g_integer
403 ! use m7b, only: g => g_real
404 ! interface g
405 ! procedure :: s
406 ! end interface
407 ! private :: s
408 !contains
409 ! subroutine s(x)
410 ! complex(4) :: x
411 ! end
412 ! subroutine test()
413 ! end
414 !end
416 ! Test m8 is like m7 but without renaming.
418 module m8a
419 interface g
420 module procedure s
421 end interface
422 private :: s
423 contains
424 subroutine s(x)
425 integer :: x
428 !Expect: m8a.mod
429 !module m8a
430 ! interface g
431 ! procedure :: s
432 ! end interface
433 ! private :: s
434 !contains
435 ! subroutine s(x)
436 ! integer(4) :: x
437 ! end
438 !end
440 module m8b
441 interface g
442 module procedure s
443 end interface
444 private :: s
445 contains
446 subroutine s(x)
447 real :: x
448 end subroutine
450 !Expect: m8b.mod
451 !module m8b
452 ! interface g
453 ! procedure :: s
454 ! end interface
455 ! private :: s
456 !contains
457 ! subroutine s(x)
458 ! real(4) :: x
459 ! end
460 !end
462 module m8c
463 use m8a
464 use m8b
465 interface g
466 module procedure s
467 end interface
468 private :: s
469 contains
470 subroutine s(x)
471 complex :: x
472 end subroutine
473 subroutine test()
474 real :: x
475 integer :: y
476 complex :: z
477 call g(x)
478 call g(y)
479 call g(z)
482 !Expect: m8c.mod
483 !module m8c
484 ! use m8a, only: g
485 ! use m8b, only: g
486 ! interface g
487 ! procedure :: s
488 ! end interface
489 ! private :: s
490 !contains
491 ! subroutine s(x)
492 ! complex(4) :: x
493 ! end
494 ! subroutine test()
495 ! end
496 !end
498 ! Merging a use-associated generic with a local generic
500 module m9a
501 interface g
502 module procedure s
503 end interface
504 private :: s
505 contains
506 subroutine s(x)
507 integer :: x
510 !Expect: m9a.mod
511 !module m9a
512 ! interface g
513 ! procedure :: s
514 ! end interface
515 ! private :: s
516 !contains
517 ! subroutine s(x)
518 ! integer(4) :: x
519 ! end
520 !end
522 module m9b
523 use m9a
524 interface g
525 module procedure s
526 end interface
527 private :: s
528 contains
529 subroutine s(x)
530 real :: x
532 subroutine test()
533 call g(1)
534 call g(1.0)
537 !Expect: m9b.mod
538 !module m9b
539 ! use m9a,only:g
540 ! interface g
541 ! procedure::s
542 ! end interface
543 ! private::s
544 !contains
545 ! subroutine s(x)
546 ! real(4)::x
547 ! end
548 ! subroutine test()
549 ! end
550 !end
552 ! Verify that equivalent names are used when generic operators are merged
554 module m10a
555 interface operator(.ne.)
556 end interface
558 !Expect: m10a.mod
559 !module m10a
560 ! interface operator(.ne.)
561 ! end interface
562 !end
564 module m10b
565 interface operator(<>)
566 end interface
568 !Expect: m10b.mod
569 !module m10b
570 ! interface operator(<>)
571 ! end interface
572 !end
574 module m10c
575 use m10a
576 use m10b
577 interface operator(/=)
578 end interface
580 !Expect: m10c.mod
581 !module m10c
582 ! use m10a,only:operator(.ne.)
583 ! use m10b,only:operator(.ne.)
584 ! interface operator(.ne.)
585 ! end interface
586 !end
588 module m10d
589 use m10a
590 use m10c
591 private :: operator(<>)
593 !Expect: m10d.mod
594 !module m10d
595 ! use m10a,only:operator(.ne.)
596 ! use m10c,only:operator(.ne.)
597 ! interface operator(.ne.)
598 ! end interface
599 ! private::operator(.ne.)
600 !end
602 module m11a
603 contains
604 subroutine s1()
607 !Expect: m11a.mod
608 !module m11a
609 !contains
610 ! subroutine s1()
611 ! end
612 !end
614 module m11b
615 use m11a
616 interface g
617 module procedure s1
618 end interface
620 !Expect: m11b.mod
621 !module m11b
622 ! use m11a,only:s1
623 ! interface g
624 ! procedure::s1
625 ! end interface
626 !end