AMDGPU: Allow f16/bf16 for DS_READ_TR16_B64 gfx950 builtins (#118297)
[llvm-project.git] / flang / test / Semantics / modfile32.f90
blob2878614b9041608eeeb4a27ee057e3a419b4278b
1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Resolution of generic names in expressions.
3 ! Test by using generic function in a specification expression that needs
4 ! to be written to a .mod file.
6 ! Resolve based on number of arguments
7 module m1
8 interface f
9 pure integer(8) function f1(x)
10 real, intent(in) :: x
11 end
12 pure integer(8) function f2(x, y)
13 real, intent(in) :: x, y
14 end
15 pure integer(8) function f3(x, y, z, w)
16 real, intent(in) :: x, y, z, w
17 optional :: w
18 end
19 end interface
20 contains
21 subroutine s1(x, z)
22 real :: z(f(x)) ! resolves to f1
23 end
24 subroutine s2(x, y, z)
25 real :: z(f(x, y)) ! resolves to f2
26 end
27 subroutine s3(x, y, z, w)
28 real :: w(f(x, y, z)) ! resolves to f3
29 end
30 subroutine s4(x, y, z, w, u)
31 real :: u(f(x, y, z, w)) ! resolves to f3
32 end
33 end
34 !Expect: m1.mod
35 !module m1
36 ! interface
37 ! pure function f1(x)
38 ! real(4), intent(in) :: x
39 ! integer(8) :: f1
40 ! end
41 ! end interface
42 ! interface
43 ! pure function f2(x, y)
44 ! real(4), intent(in) :: x
45 ! real(4), intent(in) :: y
46 ! integer(8) :: f2
47 ! end
48 ! end interface
49 ! interface
50 ! pure function f3(x, y, z, w)
51 ! real(4), intent(in) :: x
52 ! real(4), intent(in) :: y
53 ! real(4), intent(in) :: z
54 ! real(4), intent(in), optional :: w
55 ! integer(8) :: f3
56 ! end
57 ! end interface
58 ! interface f
59 ! procedure :: f1
60 ! procedure :: f2
61 ! procedure :: f3
62 ! end interface
63 !contains
64 ! subroutine s1(x, z)
65 ! real(4) :: x
66 ! real(4) :: z(1_8:f1(x))
67 ! end
68 ! subroutine s2(x, y, z)
69 ! real(4) :: x
70 ! real(4) :: y
71 ! real(4) :: z(1_8:f2(x, y))
72 ! end
73 ! subroutine s3(x, y, z, w)
74 ! real(4) :: x
75 ! real(4) :: y
76 ! real(4) :: z
77 ! real(4) :: w(1_8:f3(x, y, z))
78 ! end
79 ! subroutine s4(x, y, z, w, u)
80 ! real(4) :: x
81 ! real(4) :: y
82 ! real(4) :: z
83 ! real(4) :: w
84 ! real(4) :: u(1_8:f3(x, y, z, w))
85 ! end
86 !end
88 ! Resolve based on type or kind
89 module m2
90 interface f
91 pure integer(8) function f_real4(x)
92 real(4), intent(in) :: x
93 end
94 pure integer(8) function f_real8(x)
95 real(8), intent(in) :: x
96 end
97 pure integer(8) function f_integer(x)
98 integer, intent(in) :: x
99 end
100 end interface
101 contains
102 subroutine s1(x, y)
103 real(4) :: x
104 real :: y(f(x)) ! resolves to f_real4
106 subroutine s2(x, y)
107 real(8) :: x
108 real :: y(f(x)) ! resolves to f_real8
110 subroutine s3(x, y)
111 integer :: x
112 real :: y(f(x)) ! resolves to f_integer
115 !Expect: m2.mod
116 !module m2
117 ! interface
118 ! pure function f_real4(x)
119 ! real(4), intent(in) :: x
120 ! integer(8) :: f_real4
121 ! end
122 ! end interface
123 ! interface
124 ! pure function f_real8(x)
125 ! real(8), intent(in) :: x
126 ! integer(8) :: f_real8
127 ! end
128 ! end interface
129 ! interface
130 ! pure function f_integer(x)
131 ! integer(4), intent(in) :: x
132 ! integer(8) :: f_integer
133 ! end
134 ! end interface
135 ! interface f
136 ! procedure :: f_real4
137 ! procedure :: f_real8
138 ! procedure :: f_integer
139 ! end interface
140 !contains
141 ! subroutine s1(x, y)
142 ! real(4) :: x
143 ! real(4) :: y(1_8:f_real4(x))
144 ! end
145 ! subroutine s2(x, y)
146 ! real(8) :: x
147 ! real(4) :: y(1_8:f_real8(x))
148 ! end
149 ! subroutine s3(x, y)
150 ! integer(4) :: x
151 ! real(4) :: y(1_8:f_integer(x))
152 ! end
153 !end
155 ! Resolve based on rank
156 module m3a
157 interface f
158 procedure :: f_elem
159 procedure :: f_vector
160 end interface
161 contains
162 pure integer(8) elemental function f_elem(x) result(result)
163 real, intent(in) :: x
164 result = 1_8
166 pure integer(8) function f_vector(x) result(result)
167 real, intent(in) :: x(:)
168 result = 2_8
171 !Expect: m3a.mod
172 !module m3a
173 ! interface f
174 ! procedure :: f_elem
175 ! procedure :: f_vector
176 ! end interface
177 !contains
178 ! elemental pure function f_elem(x) result(result)
179 ! real(4), intent(in) :: x
180 ! integer(8) :: result
181 ! end
182 ! pure function f_vector(x) result(result)
183 ! real(4), intent(in) :: x(:)
184 ! integer(8) :: result
185 ! end
186 !end
188 module m3b
189 use m3a
190 contains
191 subroutine s1(x, y)
192 real :: x
193 real :: y(f(x)) ! resolves to f_elem
195 subroutine s2(x, y)
196 real :: x(10)
197 real :: y(f(x)) ! resolves to f_vector (preferred over elemental one)
199 subroutine s3(x, y)
200 real :: x(10, 10)
201 real :: y(ubound(f(x), 1)) ! resolves to f_elem
204 !Expect: m3b.mod
205 !module m3b
206 ! use m3a, only: f
207 ! use m3a, only: f_elem
208 ! use m3a, only: f_vector
209 !contains
210 ! subroutine s1(x, y)
211 ! real(4) :: x
212 ! real(4) :: y(1_8:f_elem(x))
213 ! end
214 ! subroutine s2(x, y)
215 ! real(4) :: x(1_8:10_8)
216 ! real(4) :: y(1_8:f_vector(x))
217 ! end
218 ! subroutine s3(x, y)
219 ! real(4) :: x(1_8:10_8, 1_8:10_8)
220 ! real(4) :: y(1_8:10_8)
221 ! end
222 !end
224 ! Resolve defined unary operator based on type
225 module m4
226 interface operator(.foo.)
227 pure integer(8) function f_real(x)
228 real, intent(in) :: x
230 pure integer(8) function f_integer(x)
231 integer, intent(in) :: x
233 end interface
234 contains
235 subroutine s1(x, y)
236 real :: x
237 real :: y(.foo. x) ! resolves to f_real
239 subroutine s2(x, y)
240 integer :: x
241 real :: y(.foo. x) ! resolves to f_integer
244 !Expect: m4.mod
245 !module m4
246 ! interface
247 ! pure function f_real(x)
248 ! real(4), intent(in) :: x
249 ! integer(8) :: f_real
250 ! end
251 ! end interface
252 ! interface
253 ! pure function f_integer(x)
254 ! integer(4), intent(in) :: x
255 ! integer(8) :: f_integer
256 ! end
257 ! end interface
258 ! interface operator(.foo.)
259 ! procedure :: f_real
260 ! procedure :: f_integer
261 ! end interface
262 !contains
263 ! subroutine s1(x, y)
264 ! real(4) :: x
265 ! real(4) :: y(1_8:f_real(x))
266 ! end
267 ! subroutine s2(x, y)
268 ! integer(4) :: x
269 ! real(4) :: y(1_8:f_integer(x))
270 ! end
271 !end
273 ! Resolve defined binary operator based on type
274 module m5
275 interface operator(.foo.)
276 pure integer(8) function f1(x, y)
277 real, intent(in) :: x
278 real, intent(in) :: y
280 pure integer(8) function f2(x, y)
281 real, intent(in) :: x
282 complex, intent(in) :: y
284 end interface
285 contains
286 subroutine s1(x, y)
287 complex :: x
288 real :: y(1.0 .foo. x) ! resolves to f2
290 subroutine s2(x, y)
291 real :: x
292 real :: y(1.0 .foo. x) ! resolves to f1
295 !Expect: m5.mod
296 !module m5
297 ! interface
298 ! pure function f1(x, y)
299 ! real(4), intent(in) :: x
300 ! real(4), intent(in) :: y
301 ! integer(8) :: f1
302 ! end
303 ! end interface
304 ! interface
305 ! pure function f2(x, y)
306 ! real(4), intent(in) :: x
307 ! complex(4), intent(in) :: y
308 ! integer(8) :: f2
309 ! end
310 ! end interface
311 ! interface operator(.foo.)
312 ! procedure :: f1
313 ! procedure :: f2
314 ! end interface
315 !contains
316 ! subroutine s1(x, y)
317 ! complex(4) :: x
318 ! real(4) :: y(1_8:f2(1._4, x))
319 ! end
320 ! subroutine s2(x, y)
321 ! real(4) :: x
322 ! real(4) :: y(1_8:f1(1._4, x))
323 ! end
324 !end