xref: /llvm-project/flang/test/Semantics/modfile33.f90 (revision a3e9d3c2c7e9f8766bf03c63e43675258cc611ee)
1! RUN: %python %S/test_modfile.py %s %flang_fc1 -flogical-abbreviations -fxor-operator
2
3! Resolution of user-defined operators in expressions.
4! Test by using generic function in a specification expression that needs
5! to be written to a .mod file.
6
7! Numeric operators
8module m1
9  type :: t
10    sequence
11    logical :: x
12  end type
13  interface operator(+)
14    pure integer(8) function add_ll(x, y)
15      logical, intent(in) :: x, y
16    end
17    pure integer(8) function add_li(x, y)
18      logical, intent(in) :: x
19      integer, intent(in) :: y
20    end
21    pure integer(8) function add_tt(x, y)
22      import :: t
23      type(t), intent(in) :: x, y
24    end
25  end interface
26  interface operator(/)
27    pure integer(8) function div_tz(x, y)
28      import :: t
29      type(t), intent(in) :: x
30      complex, intent(in) :: y
31    end
32    pure integer(8) function div_ct(x, y)
33      import :: t
34      character(10), intent(in) :: x
35      type(t), intent(in) :: y
36    end
37  end interface
38contains
39  subroutine s1(x, y, z)
40    logical :: x, y
41    real :: z(x + y)  ! resolves to add_ll
42  end
43  subroutine s2(x, y, z)
44    logical :: x
45    integer :: y
46    real :: z(x + y)  ! resolves to add_li
47  end
48  subroutine s3(x, y, z)
49    type(t) :: x
50    complex :: y
51    real :: z(x / y)  ! resolves to div_tz
52  end
53  subroutine s4(x, y, z)
54    character(10) :: x
55    type(t) :: y
56    real :: z(x / y)  ! resolves to div_ct
57  end
58end
59
60!Expect: m1.mod
61!module m1
62! type :: t
63!  sequence
64!  logical(4) :: x
65! end type
66! interface
67!  pure function add_ll(x, y)
68!   logical(4), intent(in) :: x
69!   logical(4), intent(in) :: y
70!   integer(8) :: add_ll
71!  end
72! end interface
73! interface
74!  pure function add_li(x, y)
75!   logical(4), intent(in) :: x
76!   integer(4), intent(in) :: y
77!   integer(8) :: add_li
78!  end
79! end interface
80! interface
81!  pure function add_tt(x, y)
82!   import :: t
83!   type(t), intent(in) :: x
84!   type(t), intent(in) :: y
85!   integer(8) :: add_tt
86!  end
87! end interface
88! interface
89!  pure function div_tz(x, y)
90!   import :: t
91!   type(t), intent(in) :: x
92!   complex(4), intent(in) :: y
93!   integer(8) :: div_tz
94!  end
95! end interface
96! interface
97!  pure function div_ct(x, y)
98!   import :: t
99!   character(10_4, 1), intent(in) :: x
100!   type(t), intent(in) :: y
101!   integer(8) :: div_ct
102!  end
103! end interface
104! interface operator(+)
105!  procedure :: add_ll
106!  procedure :: add_li
107!  procedure :: add_tt
108! end interface
109! interface operator(/)
110!  procedure :: div_tz
111!  procedure :: div_ct
112! end interface
113!contains
114! subroutine s1(x, y, z)
115!  logical(4) :: x
116!  logical(4) :: y
117!  real(4) :: z(1_8:add_ll(x, y))
118! end
119! subroutine s2(x, y, z)
120!  logical(4) :: x
121!  integer(4) :: y
122!  real(4) :: z(1_8:add_li(x, y))
123! end
124! subroutine s3(x, y, z)
125!  type(t) :: x
126!  complex(4) :: y
127!  real(4) :: z(1_8:div_tz(x, y))
128! end
129! subroutine s4(x, y, z)
130!  character(10_4, 1) :: x
131!  type(t) :: y
132!  real(4) :: z(1_8:div_ct(x, y))
133! end
134!end
135
136! Logical operators
137module m2
138  type :: t
139    sequence
140    logical :: x
141  end type
142  interface operator(.And.)
143    pure integer(8) function and_ti(x, y)
144      import :: t
145      type(t), intent(in) :: x
146      integer, intent(in) :: y
147    end
148    pure integer(8) function and_li(x, y)
149      logical, intent(in) :: x
150      integer, intent(in) :: y
151    end
152  end interface
153  ! Alternative spelling of .AND.
154  interface operator(.a.)
155    pure integer(8) function and_tt(x, y)
156      import :: t
157      type(t), intent(in) :: x, y
158    end
159  end interface
160  interface operator(.x.)
161    pure integer(8) function neqv_tt(x, y)
162      import :: t
163      type(t), intent(in) :: x, y
164    end
165  end interface
166  interface operator(.neqv.)
167    pure integer(8) function neqv_rr(x, y)
168      real, intent(in) :: x, y
169    end
170  end interface
171contains
172  subroutine s1(x, y, z)
173    type(t) :: x
174    integer :: y
175    real :: z(x .and. y)  ! resolves to and_ti
176  end
177  subroutine s2(x, y, z)
178    logical :: x
179    integer :: y
180    real :: z(x .a. y)  ! resolves to and_li
181  end
182  subroutine s3(x, y, z)
183    type(t) :: x, y
184    real :: z(x .and. y)  ! resolves to and_tt
185  end
186  subroutine s4(x, y, z)
187    type(t) :: x, y
188    real :: z(x .neqv. y)  ! resolves to neqv_tt
189  end
190  subroutine s5(x, y, z)
191    real :: x, y
192    real :: z(x .xor. y)  ! resolves to neqv_rr
193  end
194end
195
196!Expect: m2.mod
197!module m2
198! type :: t
199!  sequence
200!  logical(4) :: x
201! end type
202! interface
203!  pure function and_ti(x, y)
204!   import :: t
205!   type(t), intent(in) :: x
206!   integer(4), intent(in) :: y
207!   integer(8) :: and_ti
208!  end
209! end interface
210! interface
211!  pure function and_li(x, y)
212!   logical(4), intent(in) :: x
213!   integer(4), intent(in) :: y
214!   integer(8) :: and_li
215!  end
216! end interface
217! interface
218!  pure function and_tt(x, y)
219!   import :: t
220!   type(t), intent(in) :: x
221!   type(t), intent(in) :: y
222!   integer(8) :: and_tt
223!  end
224! end interface
225! interface
226!  pure function neqv_tt(x, y)
227!   import :: t
228!   type(t), intent(in) :: x
229!   type(t), intent(in) :: y
230!   integer(8) :: neqv_tt
231!  end
232! end interface
233! interface
234!  pure function neqv_rr(x, y)
235!   real(4), intent(in) :: x
236!   real(4), intent(in) :: y
237!   integer(8) :: neqv_rr
238!  end
239! end interface
240! interface operator( .and.)
241!  procedure :: and_ti
242!  procedure :: and_li
243!  procedure :: and_tt
244! end interface
245! interface operator(.x.)
246!  procedure :: neqv_tt
247!  procedure :: neqv_rr
248! end interface
249!contains
250! subroutine s1(x, y, z)
251!  type(t) :: x
252!  integer(4) :: y
253!  real(4) :: z(1_8:and_ti(x, y))
254! end
255! subroutine s2(x, y, z)
256!  logical(4) :: x
257!  integer(4) :: y
258!  real(4) :: z(1_8:and_li(x, y))
259! end
260! subroutine s3(x, y, z)
261!  type(t) :: x
262!  type(t) :: y
263!  real(4) :: z(1_8:and_tt(x, y))
264! end
265! subroutine s4(x, y, z)
266!  type(t) :: x
267!  type(t) :: y
268!  real(4) :: z(1_8:neqv_tt(x, y))
269! end
270! subroutine s5(x, y, z)
271!  real(4) :: x
272!  real(4) :: y
273!  real(4) :: z(1_8:neqv_rr(x, y))
274! end
275!end
276
277! Relational operators
278module m3
279  type :: t
280    sequence
281    logical :: x
282  end type
283  interface operator(<>)
284    pure integer(8) function ne_it(x, y)
285      import :: t
286      integer, intent(in) :: x
287      type(t), intent(in) :: y
288    end
289  end interface
290  interface operator(/=)
291    pure integer(8) function ne_tt(x, y)
292      import :: t
293      type(t), intent(in) :: x, y
294    end
295  end interface
296  interface operator(.ne.)
297    pure integer(8) function ne_ci(x, y)
298      character(len=*), intent(in) :: x
299      integer, intent(in) :: y
300    end
301  end interface
302contains
303  subroutine s1(x, y, z)
304    integer :: x
305    type(t) :: y
306    real :: z(x /= y)  ! resolves to ne_it
307  end
308  subroutine s2(x, y, z)
309    type(t) :: x
310    type(t) :: y
311    real :: z(x .ne. y)  ! resolves to ne_tt
312  end
313  subroutine s3(x, y, z)
314    character(len=*) :: x
315    integer :: y
316    real :: z(x <> y)  ! resolves to ne_ci
317  end
318end
319
320!Expect: m3.mod
321!module m3
322! type :: t
323!  sequence
324!  logical(4) :: x
325! end type
326! interface
327!  pure function ne_it(x, y)
328!   import :: t
329!   integer(4), intent(in) :: x
330!   type(t), intent(in) :: y
331!   integer(8) :: ne_it
332!  end
333! end interface
334! interface
335!  pure function ne_tt(x, y)
336!   import :: t
337!   type(t), intent(in) :: x
338!   type(t), intent(in) :: y
339!   integer(8) :: ne_tt
340!  end
341! end interface
342! interface
343!  pure function ne_ci(x, y)
344!   character(*, 1), intent(in) :: x
345!   integer(4), intent(in) :: y
346!   integer(8) :: ne_ci
347!  end
348! end interface
349! interface operator(<>)
350!  procedure :: ne_it
351!  procedure :: ne_tt
352!  procedure :: ne_ci
353! end interface
354!contains
355! subroutine s1(x, y, z)
356!  integer(4) :: x
357!  type(t) :: y
358!  real(4) :: z(1_8:ne_it(x, y))
359! end
360! subroutine s2(x, y, z)
361!  type(t) :: x
362!  type(t) :: y
363!  real(4) :: z(1_8:ne_tt(x, y))
364! end
365! subroutine s3(x, y, z)
366!  character(*, 1) :: x
367!  integer(4) :: y
368!  real(4) :: z(1_8:ne_ci(x, y))
369! end
370!end
371
372! Concatenation
373module m4
374  type :: t
375    sequence
376    logical :: x
377  end type
378  interface operator(//)
379    pure integer(8) function concat_12(x, y)
380      character(len=*,kind=1), intent(in) :: x
381      character(len=*,kind=2), intent(in) :: y
382    end
383    pure integer(8) function concat_int_real(x, y)
384      integer, intent(in) :: x
385      real, intent(in) :: y
386    end
387  end interface
388contains
389  subroutine s1(x, y, z)
390    character(len=*,kind=1) :: x
391    character(len=*,kind=2) :: y
392    real :: z(x // y)  ! resolves to concat_12
393  end
394  subroutine s2(x, y, z)
395    integer :: x
396    real :: y
397    real :: z(x // y)  ! resolves to concat_int_real
398  end
399end
400!Expect: m4.mod
401!module m4
402! type :: t
403!  sequence
404!  logical(4) :: x
405! end type
406! interface
407!  pure function concat_12(x, y)
408!   character(*, 1), intent(in) :: x
409!   character(*, 2), intent(in) :: y
410!   integer(8) :: concat_12
411!  end
412! end interface
413! interface
414!  pure function concat_int_real(x, y)
415!   integer(4), intent(in) :: x
416!   real(4), intent(in) :: y
417!   integer(8) :: concat_int_real
418!  end
419! end interface
420! interface operator(//)
421!  procedure :: concat_12
422!  procedure :: concat_int_real
423! end interface
424!contains
425! subroutine s1(x, y, z)
426!  character(*, 1) :: x
427!  character(*, 2) :: y
428!  real(4) :: z(1_8:concat_12(x, y))
429! end
430! subroutine s2(x, y, z)
431!  integer(4) :: x
432!  real(4) :: y
433!  real(4) :: z(1_8:concat_int_real(x, y))
434! end
435!end
436
437! Unary operators
438module m5
439  type :: t
440  end type
441  interface operator(+)
442    pure integer(8) function plus_l(x)
443      logical, intent(in) :: x
444    end
445  end interface
446  interface operator(-)
447    pure integer(8) function minus_t(x)
448      import :: t
449      type(t), intent(in) :: x
450    end
451  end interface
452  interface operator(.not.)
453    pure integer(8) function not_t(x)
454      import :: t
455      type(t), intent(in) :: x
456    end
457    pure integer(8) function not_real(x)
458      real, intent(in) :: x
459    end
460  end interface
461contains
462  subroutine s1(x, y)
463    logical :: x
464    real :: y(+x)  ! resolves_to plus_l
465  end
466  subroutine s2(x, y)
467    type(t) :: x
468    real :: y(-x)  ! resolves_to minus_t
469  end
470  subroutine s3(x, y)
471    type(t) :: x
472    real :: y(.not. x)  ! resolves to not_t
473  end
474  subroutine s4(x, y)
475    real :: y(.not. x)  ! resolves to not_real
476  end
477end
478
479!Expect: m5.mod
480!module m5
481! type :: t
482! end type
483! interface
484!  pure function plus_l(x)
485!   logical(4), intent(in) :: x
486!   integer(8) :: plus_l
487!  end
488! end interface
489! interface
490!  pure function minus_t(x)
491!   import :: t
492!   type(t), intent(in) :: x
493!   integer(8) :: minus_t
494!  end
495! end interface
496! interface
497!  pure function not_t(x)
498!   import :: t
499!   type(t), intent(in) :: x
500!   integer(8) :: not_t
501!  end
502! end interface
503! interface
504!  pure function not_real(x)
505!   real(4), intent(in) :: x
506!   integer(8) :: not_real
507!  end
508! end interface
509! interface operator(+)
510!  procedure :: plus_l
511! end interface
512! interface operator(-)
513!  procedure :: minus_t
514! end interface
515! interface operator( .not.)
516!  procedure :: not_t
517!  procedure :: not_real
518! end interface
519!contains
520! subroutine s1(x, y)
521!  logical(4) :: x
522!  real(4) :: y(1_8:plus_l(x))
523! end
524! subroutine s2(x, y)
525!  type(t) :: x
526!  real(4) :: y(1_8:minus_t(x))
527! end
528! subroutine s3(x, y)
529!  type(t) :: x
530!  real(4) :: y(1_8:not_t(x))
531! end
532! subroutine s4(x, y)
533!  real(4) :: x
534!  real(4) :: y(1_8:not_real(x))
535! end
536!end
537
538! Resolved based on shape
539module m6
540  interface operator(+)
541    pure integer(8) function add(x, y)
542      real, intent(in) :: x(:, :)
543      real, intent(in) :: y(:, :, :)
544    end
545  end interface
546contains
547  subroutine s1(n, x, y, z, a, b)
548    integer(8) :: n
549    real :: x
550    real :: y(4, n)
551    real :: z(2, 2, 2)
552    real :: a(size(x+y))  ! intrinsic +
553    real :: b(y+z)  ! resolves to add
554  end
555end
556
557!Expect: m6.mod
558!module m6
559! interface
560!  pure function add(x, y)
561!   real(4), intent(in) :: x(:, :)
562!   real(4), intent(in) :: y(:, :, :)
563!   integer(8) :: add
564!  end
565! end interface
566! interface operator(+)
567!  procedure :: add
568! end interface
569!contains
570! subroutine s1(n, x, y, z, a, b)
571!  integer(8) :: n
572!  real(4) :: x
573!  real(4) :: y(1_8:4_8, 1_8:n)
574!  real(4) :: z(1_8:2_8, 1_8:2_8, 1_8:2_8)
575!  real(4) :: a(1_8:int(int(4_8*size(y,dim=2,kind=8),kind=4),kind=8))
576!  real(4) :: b(1_8:add(y, z))
577! end
578!end
579
580! Parameterized derived type
581module m7
582  type :: t(k)
583    integer, kind :: k
584    real(k) :: a
585  end type
586  interface operator(+)
587    pure integer(8) function f1(x, y)
588      import :: t
589      type(t(4)), intent(in) :: x, y
590    end
591    pure integer(8) function f2(x, y)
592      import :: t
593      type(t(8)), intent(in) :: x, y
594    end
595  end interface
596contains
597  subroutine s1(x, y, z)
598    type(t(4)) :: x, y
599    real :: z(x + y)  ! resolves to f1
600  end
601  subroutine s2(x, y, z)
602    type(t(8)) :: x, y
603    real :: z(x + y)  ! resolves to f2
604  end
605end
606
607!Expect: m7.mod
608!module m7
609! type :: t(k)
610!  integer(4), kind :: k
611!  real(int(int(k,kind=4),kind=8))::a
612! end type
613! interface
614!  pure function f1(x, y)
615!   import :: t
616!   type(t(k=4_4)), intent(in) :: x
617!   type(t(k=4_4)), intent(in) :: y
618!   integer(8) :: f1
619!  end
620! end interface
621! interface
622!  pure function f2(x, y)
623!   import :: t
624!   type(t(k=8_4)), intent(in) :: x
625!   type(t(k=8_4)), intent(in) :: y
626!   integer(8) :: f2
627!  end
628! end interface
629! interface operator(+)
630!  procedure :: f1
631!  procedure :: f2
632! end interface
633!contains
634! subroutine s1(x, y, z)
635!  type(t(k=4_4)) :: x
636!  type(t(k=4_4)) :: y
637!  real(4) :: z(1_8:f1(x, y))
638! end
639! subroutine s2(x, y, z)
640!  type(t(k=8_4)) :: x
641!  type(t(k=8_4)) :: y
642!  real(4) :: z(1_8:f2(x, y))
643! end
644!end
645