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