[TableGen][SystemZ] Correctly check the range of a leaf immediate (#119931)
[llvm-project.git] / flang / test / Semantics / modfile03.f90
blobeb3136f0aa8bce3a2ab7b765c3abcec12d19fda8
1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Check modfile generation with use-association.
4 module m1
5 integer :: x1
6 integer, private :: x2
7 end
8 !Expect: m1.mod
9 !module m1
10 !integer(4)::x1
11 !integer(4),private::x2
12 !end
14 module m2
15 use m1
16 integer :: y1
17 end
18 !Expect: m2.mod
19 !module m2
20 !use m1,only:x1
21 !integer(4)::y1
22 !end
24 module m3
25 use m2, z1 => x1
26 end
27 !Expect: m3.mod
28 !module m3
29 !use m2,only:y1
30 !use m2,only:z1=>x1
31 !end
33 module m4
34 use m1
35 use m2
36 end
37 !Expect: m4.mod
38 !module m4
39 !use m1,only:x1
40 !use m2,only:y1
41 !end
43 module m5a
44 integer, parameter :: k1 = 4
45 integer :: l1 = 2
46 type t1
47 real :: a
48 end type
49 contains
50 pure integer function f1(i)
51 value :: i
52 f1 = i
53 end
54 end
55 !Expect: m5a.mod
56 !module m5a
57 ! integer(4),parameter::k1=4_4
58 ! integer(4)::l1
59 ! type::t1
60 ! real(4)::a
61 ! end type
62 !contains
63 ! pure function f1(i)
64 ! integer(4),value::i
65 ! integer(4)::f1
66 ! end
67 !end
69 module m5b
70 use m5a, only: k2 => k1, l2 => l1, f2 => f1
71 interface
72 subroutine s(x, y)
73 import f2, l2
74 character(l2, k2) :: x
75 character(f2(l2)) :: y
76 end subroutine
77 end interface
78 end
79 !Expect: m5b.mod
80 !module m5b
81 ! use m5a,only:k2=>k1
82 ! use m5a,only:l2=>l1
83 ! use m5a,only:f2=>f1
84 ! interface
85 ! subroutine s(x,y)
86 ! import::f2
87 ! import::l2
88 ! character(l2,4)::x
89 ! character(f2(l2),1)::y
90 ! end
91 ! end interface
92 !end
94 module m6a
95 type t1
96 end type
97 end
98 !Expect: m6a.mod
99 !module m6a
100 ! type::t1
101 ! end type
102 !end
104 module m6b
105 use m6a, only: t2 => t1
106 contains
107 subroutine s(x)
108 type(t2) :: x
111 !Expect: m6b.mod
112 !module m6b
113 ! use m6a,only:t2=>t1
114 !contains
115 ! subroutine s(x)
116 ! type(t2)::x
117 ! end
118 !end
120 module m6c
121 use m6a, only: t2 => t1
122 type, extends(t2) :: t
123 end type
125 !Expect: m6c.mod
126 !module m6c
127 ! use m6a,only:t2=>t1
128 ! type,extends(t2)::t
129 ! end type
130 !end
132 module m6d
133 use m6a, only: t2 => t1
134 type(t2), parameter :: p = t2()
136 !Expect: m6d.mod
137 !module m6d
138 ! use m6a,only:t2=>t1
139 ! type(t2),parameter::p=t2()
140 !end
142 module m6e
143 use m6a, only: t2 => t1
144 interface
145 subroutine s(x)
146 import t2
147 type(t2) :: x
148 end subroutine
149 end interface
151 !Expect: m6e.mod
152 !module m6e
153 ! use m6a,only:t2=>t1
154 ! interface
155 ! subroutine s(x)
156 ! import::t2
157 ! type(t2)::x
158 ! end
159 ! end interface
160 !end
162 module m7a
163 real :: x
165 !Expect: m7a.mod
166 !module m7a
167 ! real(4)::x
168 !end
170 module m7b
171 use m7a
172 private
174 !Expect: m7b.mod
175 !module m7b
176 ! use m7a,only:x
177 ! private::x
178 !end
180 module m8a
181 private foo
182 type t
183 contains
184 procedure, nopass :: foo
185 end type
186 contains
187 pure integer function foo(n)
188 integer, intent(in) :: n
189 foo = n
192 !Expect: m8a.mod
193 !module m8a
194 !type::t
195 !contains
196 !procedure,nopass::foo
197 !end type
198 !private::foo
199 !contains
200 !pure function foo(n)
201 !integer(4),intent(in)::n
202 !integer(4)::foo
203 !end
204 !end
206 module m8b
207 use m8a
208 contains
209 subroutine foo(x,a)
210 type(t), intent(in) :: x
211 real a(x%foo(10))
214 !Expect: m8b.mod
215 !module m8b
216 !use m8a,only:m8a$foo=>foo
217 !use m8a,only:t
218 !private::m8a$foo
219 !contains
220 !subroutine foo(x,a)
221 !type(t),intent(in)::x
222 !real(4)::a(1_8:int(m8a$foo(10_4),kind=8))
223 !end
224 !end
226 module m9a
227 private
228 public t
229 type t
230 integer n
231 contains
232 procedure f
233 end type
234 contains
235 pure integer function f(x, k)
236 class(t), intent(in) :: x
237 integer, intent(in) :: k
238 f = x%n + k
241 !Expect: m9a.mod
242 !module m9a
243 !type::t
244 !integer(4)::n
245 !contains
246 !procedure::f
247 !end type
248 !private::f
249 !contains
250 !pure function f(x,k)
251 !class(t),intent(in)::x
252 !integer(4),intent(in)::k
253 !integer(4)::f
254 !end
255 !end
257 module m9b
258 use m9a
259 contains
260 subroutine s(x, y)
261 class(t), intent(in) :: x
262 real y(x%f(x%n))
265 !Expect: m9b.mod
266 !module m9b
267 !use m9a,only:t
268 !contains
269 !subroutine s(x,y)
270 !class(t),intent(in)::x
271 !real(4)::y(1_8:int(x%f(x%n),kind=8))
272 !end
273 !end