xref: /llvm-project/flang/test/Semantics/modfile07.f90 (revision a3e9d3c2c7e9f8766bf03c63e43675258cc611ee)
1! RUN: %python %S/test_modfile.py %s %flang_fc1
2! Check modfile generation for generic interfaces
3module 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
46contains
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
53end
54!Expect: m1.mod
55!module m1
56! interface
57!  function s1(x,y)
58!   real(4),intent(in)::x
59!   logical(4),intent(in)::y
60!   real(4)::s1
61!  end
62! end interface
63! interface
64!  function s2(x,y)
65!   complex(4),intent(in)::x
66!   logical(4),intent(in)::y
67!   complex(4)::s2
68!  end
69! end interface
70! interface
71!  function f1(x,y)
72!   real(4),intent(in)::x
73!   logical(4),intent(in)::y
74!   logical(4)::f1
75!  end
76! end interface
77! interface
78!  function f2(x,y)
79!   complex(4),intent(in)::x
80!   logical(4),intent(in)::y
81!   logical(4)::f2
82!  end
83! end interface
84! interface
85!  function f3(x,y)
86!   integer(4),intent(in)::x
87!   logical(4),intent(in)::y
88!   logical(4)::f3
89!  end
90! end interface
91! interface foo
92!  procedure::s1
93!  procedure::s2
94! end interface
95! interface operator(+)
96!  procedure::s1
97!  procedure::s2
98! end interface
99! interface operator(/=)
100!  procedure::f1
101!  procedure::f2
102!  procedure::f3
103! end interface
104! private::operator(/=)
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
129
130module m1b
131  use m1
132end
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
147
148module 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(+)
153end
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
161
162module m2
163  interface foo
164    procedure foo
165  end interface
166contains
167  complex function foo()
168    foo = 1.0
169  end
170end
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
181
182module 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
191end
192!Expect: m2b.mod
193!module m2b
194! type::foo
195!  real(4)::x
196! end type
197! interface foo
198! end interface
199! interface bar
200! end interface
201! private::bar
202!end
203
204! Test interface nested inside another interface
205module 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
218end
219!Expect: m3.mod
220!module m3
221! interface
222!  subroutine s1(f)
223!   interface
224!    function f(x)
225!     interface
226!      subroutine x()
227!      end
228!     end interface
229!     real(4)::f
230!    end
231!   end interface
232!  end
233! end interface
234! interface g
235!  procedure::s1
236! end interface
237!end
238
239module m4
240  interface foo
241    integer function foo()
242    end function
243    integer function f(x)
244    end function
245  end interface
246end
247subroutine s4
248  use m4
249  i = foo()
250end
251!Expect: m4.mod
252!module m4
253! interface
254!  function foo()
255!   integer(4)::foo
256!  end
257! end interface
258! interface
259!  function f(x)
260!   real(4)::x
261!   integer(4)::f
262!  end
263! end interface
264! interface foo
265!  procedure::foo
266!  procedure::f
267! end interface
268!end
269
270! Compile contents of m4.mod and verify it gets the same thing again.
271module m5
272 interface foo
273  procedure::foo
274  procedure::f
275 end interface
276 interface
277  function foo()
278   integer(4)::foo
279  end
280 end interface
281 interface
282  function f(x)
283   integer(4)::f
284   real(4)::x
285  end
286 end interface
287end
288!Expect: m5.mod
289!module m5
290! interface
291!  function foo()
292!   integer(4)::foo
293!  end
294! end interface
295! interface
296!  function f(x)
297!   real(4)::x
298!   integer(4)::f
299!  end
300! end interface
301! interface foo
302!  procedure::foo
303!  procedure::f
304! end interface
305!end
306
307module m6a
308  interface operator(<)
309    logical function lt(x, y)
310      logical, intent(in) :: x, y
311    end function
312  end interface
313end
314!Expect: m6a.mod
315!module m6a
316! interface
317!  function lt(x,y)
318!   logical(4),intent(in)::x
319!   logical(4),intent(in)::y
320!   logical(4)::lt
321!  end
322! end interface
323! interface operator(<)
324!  procedure::lt
325! end interface
326!end
327
328module m6b
329  use m6a, only: operator(.lt.)
330end
331!Expect: m6b.mod
332!module m6b
333! use m6a,only:operator(.lt.)
334!end
335
336module m7a
337  interface g_integer
338    module procedure s
339  end interface
340  private :: s
341contains
342  subroutine s(x)
343    integer :: x
344  end
345end
346!Expect: m7a.mod
347!module m7a
348! private :: s
349! interface g_integer
350!  procedure :: s
351! end interface
352!contains
353! subroutine s(x)
354!  integer(4) :: x
355! end
356!end
357
358module m7b
359  interface g_real
360    module procedure s
361  end interface
362  private :: s
363contains
364  subroutine s(x)
365    real :: x
366  end subroutine
367end
368!Expect: m7b.mod
369!module m7b
370! private :: s
371! interface g_real
372!  procedure :: s
373! end interface
374!contains
375! subroutine s(x)
376!  real(4) :: x
377! end
378!end
379
380module 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
387contains
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)
398  end
399end
400!Expect: m7c.mod
401!module m7c
402! use m7a, only: g => g_integer
403! use m7b, only: g => g_real
404! private :: s
405! interface g
406!  procedure :: s
407! end interface
408!contains
409! subroutine s(x)
410!  complex(4) :: x
411! end
412! subroutine test()
413! end
414!end
415
416! Test m8 is like m7 but without renaming.
417
418module m8a
419  interface g
420    module procedure s
421  end interface
422  private :: s
423contains
424  subroutine s(x)
425    integer :: x
426  end
427end
428!Expect: m8a.mod
429!module m8a
430! private :: s
431! interface g
432!  procedure :: s
433! end interface
434!contains
435! subroutine s(x)
436!  integer(4) :: x
437! end
438!end
439
440module m8b
441  interface g
442    module procedure s
443  end interface
444  private :: s
445contains
446  subroutine s(x)
447    real :: x
448  end subroutine
449end
450!Expect: m8b.mod
451!module m8b
452! private :: s
453! interface g
454!  procedure :: s
455! end interface
456!contains
457! subroutine s(x)
458!  real(4) :: x
459! end
460!end
461
462module m8c
463  use m8a
464  use m8b
465  interface g
466    module procedure s
467  end interface
468  private :: s
469contains
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)
480  end
481end
482!Expect: m8c.mod
483!module m8c
484! use m8a, only: g
485! use m8b, only: g
486! private :: s
487! interface g
488!  procedure :: s
489! end interface
490!contains
491! subroutine s(x)
492!  complex(4) :: x
493! end
494! subroutine test()
495! end
496!end
497
498! Merging a use-associated generic with a local generic
499
500module m9a
501  interface g
502    module procedure s
503  end interface
504  private :: s
505contains
506  subroutine s(x)
507    integer :: x
508  end
509end
510!Expect: m9a.mod
511!module m9a
512! private :: s
513! interface g
514!  procedure :: s
515! end interface
516!contains
517! subroutine s(x)
518!  integer(4) :: x
519! end
520!end
521
522module m9b
523  use m9a
524  interface g
525    module procedure s
526  end interface
527  private :: s
528contains
529  subroutine s(x)
530    real :: x
531  end
532  subroutine test()
533    call g(1)
534    call g(1.0)
535  end
536end
537!Expect: m9b.mod
538!module m9b
539! use m9a,only:g
540! private::s
541! interface g
542!   procedure::s
543! end interface
544!contains
545! subroutine s(x)
546!   real(4)::x
547! end
548! subroutine test()
549! end
550!end
551
552! Verify that equivalent names are used when generic operators are merged
553
554module m10a
555  interface operator(.ne.)
556  end interface
557end
558!Expect: m10a.mod
559!module m10a
560! interface operator(.ne.)
561! end interface
562!end
563
564module m10b
565  interface operator(<>)
566  end interface
567end
568!Expect: m10b.mod
569!module m10b
570! interface operator(<>)
571! end interface
572!end
573
574module m10c
575  use m10a
576  use m10b
577  interface operator(/=)
578  end interface
579end
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
587
588module m10d
589  use m10a
590  use m10c
591  private :: operator(<>)
592end
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
601
602module m11a
603contains
604  subroutine s1()
605  end
606end
607!Expect: m11a.mod
608!module m11a
609!contains
610! subroutine s1()
611! end
612!end
613
614module m11b
615  use m11a
616  interface g
617    module procedure s1
618  end interface
619end
620!Expect: m11b.mod
621!module m11b
622! use m11a,only:s1
623! interface g
624!  procedure::s1
625! end interface
626!end
627
628module m12
629  interface generic
630    module procedure specific
631  end interface
632  interface
633    module subroutine s(a1,a2)
634      character(*) a1
635      character(generic(a1)) a2
636    end
637  end interface
638 contains
639  pure integer function specific(x)
640    character(*), intent(in) :: x
641    specific = len(x)
642  end
643end
644!Expect: m12.mod
645!module m12
646! interface
647!  module subroutine s(a1,a2)
648!   character(*,1)::a1
649!   character(specific(a1),1)::a2
650!  end
651! end interface
652! interface generic
653!  procedure::specific
654! end interface
655!contains
656! pure function specific(x)
657!  character(*,1),intent(in)::x
658!  integer(4)::specific
659! end
660!end
661