• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_modfile.sh %s %t %f18
2! Check modfile generation with use-association.
3
4module m1
5  integer :: x1
6  integer, private :: x2
7end
8!Expect: m1.mod
9!module m1
10!integer(4)::x1
11!integer(4),private::x2
12!end
13
14module m2
15  use m1
16  integer :: y1
17end
18!Expect: m2.mod
19!module m2
20!use m1,only:x1
21!integer(4)::y1
22!end
23
24module m3
25  use m2, z1 => x1
26end
27!Expect: m3.mod
28!module m3
29!use m2,only:y1
30!use m2,only:z1=>x1
31!end
32
33module m4
34  use m1
35  use m2
36end
37!Expect: m4.mod
38!module m4
39!use m1,only:x1
40!use m2,only:y1
41!end
42
43module m5a
44  integer, parameter :: k1 = 4
45  integer :: l1 = 2
46  type t1
47    real :: a
48  end type
49contains
50  pure integer function f1(i)
51    value :: i
52    f1 = i
53  end
54end
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
68
69module 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
78end
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
93
94module m6a
95  type t1
96  end type
97end
98!Expect: m6a.mod
99!module m6a
100! type::t1
101! end type
102!end
103
104module m6b
105  use m6a, only: t2 => t1
106contains
107  subroutine s(x)
108    type(t2) :: x
109  end
110end
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
119
120module m6c
121  use m6a, only: t2 => t1
122  type, extends(t2) :: t
123  end type
124end
125!Expect: m6c.mod
126!module m6c
127! use m6a,only:t2=>t1
128! type,extends(t2)::t
129! end type
130!end
131
132module m6d
133  use m6a, only: t2 => t1
134  type(t2), parameter :: p = t2()
135end
136!Expect: m6d.mod
137!module m6d
138! use m6a,only:t2=>t1
139! type(t2),parameter::p=t2()
140!end
141
142module 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
150end
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
161