1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Check modfile generation with use-association.
11 !integer(4),private::x2
44 integer, parameter :: k1
= 4
50 pure
integer function f1(i
)
57 ! integer(4),parameter::k1=4_4
70 use m5a
, only
: k2
=> k1
, l2
=> l1
, f2
=> f1
74 character(l2
, k2
) :: x
75 character(f2(l2
)) :: y
89 ! character(f2(l2),1)::y
105 use m6a
, only
: t2
=> t1
113 ! use m6a,only:t2=>t1
121 use m6a
, only
: t2
=> t1
122 type, extends(t2
) :: t
127 ! use m6a,only:t2=>t1
128 ! type,extends(t2)::t
133 use m6a
, only
: t2
=> t1
134 type(t2
), parameter :: p
= t2()
138 ! use m6a,only:t2=>t1
139 ! type(t2),parameter::p=t2()
143 use m6a
, only
: t2
=> t1
153 ! use m6a,only:t2=>t1
184 procedure
, nopass
:: foo
187 pure
integer function foo(n
)
188 integer, intent(in
) :: n
196 !procedure,nopass::foo
200 !pure function foo(n)
201 !integer(4),intent(in)::n
210 type(t
), intent(in
) :: x
216 !use m8a,only:m8a$foo=>foo
221 !type(t),intent(in)::x
222 !real(4)::a(1_8:int(m8a$foo(10_4),kind=8))
235 pure
integer function f(x
, k
)
236 class(t
), intent(in
) :: x
237 integer, intent(in
) :: k
250 !pure function f(x,k)
251 !class(t),intent(in)::x
252 !integer(4),intent(in)::k
261 class(t
), intent(in
) :: x
270 !class(t),intent(in)::x
271 !real(4)::y(1_8:int(x%f(x%n),kind=8))