• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_modfile.sh %s %t %f18
2! Test that subprogram interfaces get all of the symbols that they need.
3
4module m1
5  integer(8) :: i
6  type t1
7    sequence
8    integer :: j
9  end type
10  type t2
11  end type
12end
13!Expect: m1.mod
14!module m1
15! integer(8)::i
16! type::t1
17!  sequence
18!  integer(4)::j
19! end type
20! type::t2
21! end type
22!end
23
24module m2
25  integer(8) :: k
26contains
27  subroutine s(a, j)
28    use m1
29    integer(8) :: j
30    real :: a(i:j,1:k)  ! need i from m1
31  end
32end
33!Expect: m2.mod
34!module m2
35! integer(8)::k
36!contains
37! subroutine s(a,j)
38!  use m1,only:i
39!  integer(8)::j
40!  real(4)::a(i:j,1_8:k)
41! end
42!end
43
44module m3
45  implicit none
46contains
47  subroutine s(b, n)
48    type t2
49    end type
50    type t4(l)
51      integer, len :: l
52      type(t2) :: x  ! need t2
53    end type
54    integer :: n
55    type(t4(n)) :: b
56  end
57end module
58!Expect: m3.mod
59!module m3
60!contains
61! subroutine s(b,n)
62!  integer(4)::n
63!  type::t2
64!  end type
65!  type::t4(l)
66!   integer(4),len::l
67!   type(t2)::x
68!  end type
69!  type(t4(l=n))::b
70! end
71!end
72
73module m4
74contains
75  subroutine s1(a)
76    use m1
77    common /c/x,n  ! x is needed
78    integer(8) :: n
79    real :: a(n)
80    type(t1) :: x
81  end
82end
83!Expect: m4.mod
84!module m4
85!contains
86! subroutine s1(a)
87!  use m1,only:t1
88!  type(t1)::x
89!  common/c/x,n
90!  integer(8)::n
91!  real(4)::a(1_8:n)
92! end
93!end
94
95module m5
96  type t5
97  end type
98  interface
99    subroutine s(x1,x5)
100      use m1
101      import :: t5
102      type(t1) :: x1
103      type(t5) :: x5
104    end subroutine
105  end interface
106end
107!Expect: m5.mod
108!module m5
109! type::t5
110! end type
111! interface
112!  subroutine s(x1,x5)
113!   use m1,only:t1
114!   import::t5
115!   type(t1)::x1
116!   type(t5)::x5
117!  end
118! end interface
119!end
120
121module m6
122contains
123  subroutine s(x)
124    use m1
125    type, extends(t2) :: t6
126    end type
127    type, extends(t6) :: t7
128    end type
129    type(t7) :: x
130  end
131end
132!Expect: m6.mod
133!module m6
134!contains
135! subroutine s(x)
136!  use m1,only:t2
137!  type,extends(t2)::t6
138!  end type
139!  type,extends(t6)::t7
140!  end type
141!  type(t7)::x
142! end
143!end
144
145module m7
146  type :: t5(l)
147    integer, len :: l
148  end type
149contains
150  subroutine s1(x)
151    use m1
152    type(t5(i)) :: x
153  end subroutine
154  subroutine s2(x)
155    use m1
156    character(i) :: x
157  end subroutine
158end
159!Expect: m7.mod
160!module m7
161! type::t5(l)
162!  integer(4),len::l
163! end type
164!contains
165! subroutine s1(x)
166!  use m1,only:i
167!  type(t5(l=int(i,kind=4)))::x
168! end
169! subroutine s2(x)
170!  use m1,only:i
171!  character(i,1)::x
172! end
173!end
174
175module m8
176  use m1, only: t1, t2
177  interface
178    subroutine s1(x)
179      import
180      type(t1) :: x
181    end subroutine
182    subroutine s2(x)
183      import :: t2
184      type(t2) :: x
185    end subroutine
186  end interface
187end
188!Expect: m8.mod
189!module m8
190! use m1,only:t1
191! use m1,only:t2
192! interface
193!  subroutine s1(x)
194!   import::t1
195!   type(t1)::x
196!  end
197! end interface
198! interface
199!  subroutine s2(x)
200!   import::t2
201!   type(t2)::x
202!  end
203! end interface
204!end
205