Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / modfile10.f90
blobb59fd44c985a64ab7232356e9e857f432f121eb8
1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Test writing procedure bindings in a derived type.
4 module m
5 interface
6 subroutine a(i, j)
7 integer :: i, j
8 end subroutine
9 end interface
10 type, abstract :: t
11 integer :: i
12 contains
13 procedure(a), deferred, nopass :: q
14 procedure(b), deferred, nopass :: p, r
15 end type
16 type t2
17 integer :: x
18 contains
19 private
20 final :: c
21 procedure, non_overridable :: d
22 end type
23 type, abstract :: t2a
24 contains
25 procedure(a), deferred, public, nopass :: e
26 end type
27 type t3
28 sequence
29 integer i
30 real x
31 double precision y
32 double complex z
33 end type
34 contains
35 subroutine b()
36 end subroutine
37 subroutine c(x)
38 type(t2) :: x
39 end subroutine
40 subroutine d(x)
41 class(t2) :: x
42 end subroutine
43 subroutine test
44 type(t2) :: x
45 call x%d()
46 end subroutine
47 end module
49 !Expect: m.mod
50 !module m
51 ! interface
52 ! subroutine a(i,j)
53 ! integer(4)::i
54 ! integer(4)::j
55 ! end
56 ! end interface
57 ! type,abstract::t
58 ! integer(4)::i
59 ! contains
60 ! procedure(a),deferred,nopass::q
61 ! procedure(b),deferred,nopass::p
62 ! procedure(b),deferred,nopass::r
63 ! end type
64 ! type::t2
65 ! integer(4)::x
66 ! contains
67 ! procedure,non_overridable,private::d
68 ! final::c
69 ! end type
70 ! type,abstract::t2a
71 ! contains
72 ! procedure(a),deferred,nopass::e
73 ! end type
74 ! type::t3
75 ! sequence
76 ! integer(4)::i
77 ! real(4)::x
78 ! real(8)::y
79 ! complex(8)::z
80 ! end type
81 !contains
82 ! subroutine b()
83 ! end
84 ! subroutine c(x)
85 ! type(t2)::x
86 ! end
87 ! subroutine d(x)
88 ! class(t2)::x
89 ! end
90 ! subroutine test()
91 ! end
92 !end
94 ! Ensure the type is emitted before its use
95 module m2
96 private s
97 type :: t
98 contains
99 procedure :: foo
100 end type
101 abstract interface
102 subroutine s(x)
103 import
104 type(t) :: x
105 end subroutine
106 end interface
107 contains
108 subroutine foo(x)
109 class(t) :: x
110 end subroutine
111 end module
112 !Expect: m2.mod
113 !module m2
114 ! type::t
115 ! contains
116 ! procedure::foo
117 ! end type
118 ! private::s
119 ! abstract interface
120 ! subroutine s(x)
121 ! import::t
122 ! type(t)::x
123 ! end
124 ! end interface
125 !contains
126 ! subroutine foo(x)
127 ! class(t)::x
128 ! end
129 !end