xref: /llvm-project/flang/test/Semantics/modfile35.f90 (revision dc453dcf760e6d558da3a4d7fff301baa5f37aba)
1! RUN: %python %S/test_modfile.py %s %flang_fc1
2module m1
3  type :: t1
4  contains
5    procedure, pass(x) :: p1 => f
6    procedure, non_overridable :: p2 => f
7    procedure, nopass :: p3 => f
8    generic :: operator(+) => p1
9    generic :: operator(-) => p2
10    generic :: operator(<) => p1
11    generic :: operator(.and.) => p2
12  end type
13contains
14  integer(8) pure function f(x, y)
15    class(t1), intent(in) :: x
16    integer, intent(in) :: y
17  end
18  ! Operators resolve to type-bound operators in t1
19  subroutine test1(x, y, a, b)
20    class(t1) :: x
21    integer :: y
22    real :: a(x + y)
23    real :: b(x .lt. y)
24  end
25  ! Operators resolve to type-bound operators in t1, compile-time resolvable
26  subroutine test2(x, y, a, b)
27    class(t1) :: x
28    integer :: y
29    real :: a(x - y)
30    real :: b(x .and. y)
31  end
32  ! Operators resolve to type-bound operators in t1, compile-time resolvable
33  subroutine test3(x, y, a)
34    type(t1) :: x
35    integer :: y
36    real :: a(x + y)
37  end
38end
39!Expect: m1.mod
40!module m1
41! type :: t1
42! contains
43!  procedure, pass(x) :: p1 => f
44!  procedure, non_overridable :: p2 => f
45!  procedure, nopass :: p3 => f
46!  generic :: operator(+) => p1
47!  generic :: operator(-) => p2
48!  generic :: operator(<) => p1
49!  generic :: operator(.and.) => p2
50! end type
51!contains
52! pure function f(x, y)
53!  class(t1), intent(in) :: x
54!  integer(4), intent(in) :: y
55!  integer(8) :: f
56! end
57! subroutine test1(x, y, a, b)
58!  class(t1) :: x
59!  integer(4) :: y
60!  real(4) :: a(1_8:x%p1(y))
61!  real(4) :: b(1_8:x%p1(y))
62! end
63! subroutine test2(x, y, a, b)
64!  class(t1) :: x
65!  integer(4) :: y
66!  real(4) :: a(1_8:f(x, y))
67!  real(4) :: b(1_8:f(x, y))
68! end
69! subroutine test3(x,y,a)
70!  type(t1) :: x
71!  integer(4) :: y
72!  real(4) :: a(1_8:f(x,y))
73! end
74!end
75
76module m2
77  type :: t1
78  contains
79    procedure, pass(x) :: p1 => f1
80    generic :: operator(+) => p1
81  end type
82  type, extends(t1) :: t2
83  contains
84    procedure, pass(y) :: p2 => f2
85    generic :: operator(+) => p2
86  end type
87contains
88  integer(8) pure function f1(x, y)
89    class(t1), intent(in) :: x
90    integer, intent(in) :: y
91  end
92  integer(8) pure function f2(x, y)
93    class(t1), intent(in) :: x
94    class(t2), intent(in) :: y
95  end
96  subroutine test1(x, y, a)
97    class(t1) :: x
98    integer :: y
99    real :: a(x + y)
100  end
101  ! Resolve to operator in parent class
102  subroutine test2(x, y, a)
103    class(t2) :: x
104    integer :: y
105    real :: a(x + y)
106  end
107  ! 2nd arg is passed object
108  subroutine test3(x, y, a)
109    class(t1) :: x
110    class(t2) :: y
111    real :: a(x + y)
112  end
113end
114!Expect: m2.mod
115!module m2
116! type :: t1
117! contains
118!  procedure, pass(x) :: p1 => f1
119!  generic :: operator(+) => p1
120! end type
121! type, extends(t1) :: t2
122! contains
123!  procedure, pass(y) :: p2 => f2
124!  generic :: operator(+) => p2
125! end type
126!contains
127! pure function f1(x, y)
128!  class(t1), intent(in) :: x
129!  integer(4), intent(in) :: y
130!  integer(8) :: f1
131! end
132! pure function f2(x, y)
133!  class(t1), intent(in) :: x
134!  class(t2), intent(in) :: y
135!  integer(8) :: f2
136! end
137! subroutine test1(x, y, a)
138!  class(t1) :: x
139!  integer(4) :: y
140!  real(4) :: a(1_8:x%p1(y))
141! end
142! subroutine test2(x, y, a)
143!  class(t2) :: x
144!  integer(4) :: y
145!  real(4) :: a(1_8:x%p1(y))
146! end
147! subroutine test3(x, y, a)
148!  class(t1) :: x
149!  class(t2) :: y
150!  real(4) :: a(1_8:y%p2(x))
151! end
152!end
153
154module m3
155  type :: t1
156  contains
157    procedure, pass(x) :: p1 => f1
158    procedure :: p3 => f3
159    generic :: operator(.binary.) => p1
160    generic :: operator(.unary.) => p3
161  end type
162  type, extends(t1) :: t2
163  contains
164    procedure, pass(y) :: p2 => f2
165    generic :: operator(.binary.) => p2
166  end type
167contains
168  integer(8) pure function f1(x, y)
169    class(t1), intent(in) :: x
170    integer, intent(in) :: y
171  end
172  integer(8) pure function f2(x, y)
173    class(t1), intent(in) :: x
174    class(t2), intent(in) :: y
175  end
176  integer(8) pure function f3(x)
177    class(t1), intent(in) :: x
178  end
179  subroutine test1(x, y, a)
180    class(t1) :: x
181    integer :: y
182    real :: a(x .binary. y)
183  end
184  ! Resolve to operator in parent class
185  subroutine test2(x, y, a)
186    class(t2) :: x
187    integer :: y
188    real :: a(x .binary. y)
189  end
190  ! 2nd arg is passed object
191  subroutine test3(x, y, a)
192    class(t1) :: x
193    class(t2) :: y
194    real :: a(x .binary. y)
195  end
196  subroutine test4(x, y, a)
197    class(t1) :: x
198    class(t2) :: y
199    real :: a(.unary. x + .unary. y)
200  end
201end
202!Expect: m3.mod
203!module m3
204!  type::t1
205!  contains
206!    procedure,pass(x)::p1=>f1
207!    procedure::p3=>f3
208!    generic::operator(.binary.)=>p1
209!    generic::operator(.unary.)=>p3
210!  end type
211!  type,extends(t1)::t2
212!  contains
213!    procedure,pass(y)::p2=>f2
214!    generic::operator(.binary.)=>p2
215!  end type
216!contains
217!  pure function f1(x,y)
218!    class(t1),intent(in)::x
219!    integer(4),intent(in)::y
220!    integer(8)::f1
221!  end
222!  pure function f2(x,y)
223!    class(t1),intent(in)::x
224!    class(t2),intent(in)::y
225!    integer(8)::f2
226!  end
227!  pure function f3(x)
228!    class(t1),intent(in)::x
229!    integer(8)::f3
230!  end
231!  subroutine test1(x,y,a)
232!    class(t1)::x
233!    integer(4)::y
234!    real(4)::a(1_8:x%p1(y))
235!  end
236!  subroutine test2(x,y,a)
237!    class(t2)::x
238!    integer(4)::y
239!    real(4)::a(1_8:x%p1(y))
240!  end
241!  subroutine test3(x,y,a)
242!    class(t1)::x
243!    class(t2)::y
244!    real(4)::a(1_8:y%p2(x))
245!  end
246!  subroutine test4(x,y,a)
247!    class(t1)::x
248!    class(t2)::y
249!    real(4)::a(1_8:x%p3()+y%p3())
250!  end
251!end
252