[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / modfile03.f90
blob0d15e09087b1d478cc011857419c9b68b011397e
1 ! RUN: %S/test_modfile.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! Check modfile generation with use-association.
5 module m1
6 integer :: x1
7 integer, private :: x2
8 end
9 !Expect: m1.mod
10 !module m1
11 !integer(4)::x1
12 !integer(4),private::x2
13 !end
15 module m2
16 use m1
17 integer :: y1
18 end
19 !Expect: m2.mod
20 !module m2
21 !use m1,only:x1
22 !integer(4)::y1
23 !end
25 module m3
26 use m2, z1 => x1
27 end
28 !Expect: m3.mod
29 !module m3
30 !use m2,only:y1
31 !use m2,only:z1=>x1
32 !end
34 module m4
35 use m1
36 use m2
37 end
38 !Expect: m4.mod
39 !module m4
40 !use m1,only:x1
41 !use m2,only:y1
42 !end
44 module m5a
45 integer, parameter :: k1 = 4
46 integer :: l1 = 2
47 type t1
48 real :: a
49 end type
50 contains
51 pure integer function f1(i)
52 value :: i
53 f1 = i
54 end
55 end
56 !Expect: m5a.mod
57 !module m5a
58 ! integer(4),parameter::k1=4_4
59 ! integer(4)::l1
60 ! type::t1
61 ! real(4)::a
62 ! end type
63 !contains
64 ! pure function f1(i)
65 ! integer(4),value::i
66 ! integer(4)::f1
67 ! end
68 !end
70 module m5b
71 use m5a, only: k2 => k1, l2 => l1, f2 => f1
72 interface
73 subroutine s(x, y)
74 import f2, l2
75 character(l2, k2) :: x
76 character(f2(l2)) :: y
77 end subroutine
78 end interface
79 end
80 !Expect: m5b.mod
81 !module m5b
82 ! use m5a,only:k2=>k1
83 ! use m5a,only:l2=>l1
84 ! use m5a,only:f2=>f1
85 ! interface
86 ! subroutine s(x,y)
87 ! import::f2
88 ! import::l2
89 ! character(l2,4)::x
90 ! character(f2(l2),1)::y
91 ! end
92 ! end interface
93 !end
95 module m6a
96 type t1
97 end type
98 end
99 !Expect: m6a.mod
100 !module m6a
101 ! type::t1
102 ! end type
103 !end
105 module m6b
106 use m6a, only: t2 => t1
107 contains
108 subroutine s(x)
109 type(t2) :: x
112 !Expect: m6b.mod
113 !module m6b
114 ! use m6a,only:t2=>t1
115 !contains
116 ! subroutine s(x)
117 ! type(t2)::x
118 ! end
119 !end
121 module m6c
122 use m6a, only: t2 => t1
123 type, extends(t2) :: t
124 end type
126 !Expect: m6c.mod
127 !module m6c
128 ! use m6a,only:t2=>t1
129 ! type,extends(t2)::t
130 ! end type
131 !end
133 module m6d
134 use m6a, only: t2 => t1
135 type(t2), parameter :: p = t2()
137 !Expect: m6d.mod
138 !module m6d
139 ! use m6a,only:t2=>t1
140 ! type(t2),parameter::p=t2()
141 !end
143 module m6e
144 use m6a, only: t2 => t1
145 interface
146 subroutine s(x)
147 import t2
148 type(t2) :: x
149 end subroutine
150 end interface
152 !Expect: m6e.mod
153 !module m6e
154 ! use m6a,only:t2=>t1
155 ! interface
156 ! subroutine s(x)
157 ! import::t2
158 ! type(t2)::x
159 ! end
160 ! end interface
161 !end
163 module m7a
164 real :: x
166 !Expect: m7a.mod
167 !module m7a
168 ! real(4)::x
169 !end
171 module m7b
172 use m7a
173 private
175 !Expect: m7b.mod
176 !module m7b
177 ! use m7a,only:x
178 ! private::x
179 !end