[DebugInfo][RemoveDIs] Emulate inserting insts in dbg.value sequences (#73350)
[llvm-project.git] / flang / test / Lower / program-units-fir-mangling.f90
blob36631979141a0871acc7e78c3d8bf319fec30a5d
1 ! RUN: bbc %s -o "-" -emit-fir | FileCheck %s
3 ! CHECK-LABEL: func @_QPsub() {
4 subroutine sub()
5 ! CHECK: }
6 end subroutine
8 ! CHECK-LABEL: func @_QPasubroutine() {
9 subroutine AsUbRoUtInE()
10 ! CHECK: }
11 end subroutine
13 ! CHECK-LABEL: func @_QPfoo() -> f32 {
14 function foo()
15 real(4) :: foo
16 real :: pi = 3.14159
17 ! CHECK: }
18 end function
21 ! CHECK-LABEL: func @_QPfunctn() -> f32 {
22 function functn
23 real, parameter :: pi = 3.14
24 ! CHECK: }
25 end function
28 module testMod
29 contains
30 ! CHECK-LABEL: func @_QMtestmodPsub() {
31 subroutine sub()
32 ! CHECK: }
33 end subroutine
35 ! CHECK-LABEL: func @_QMtestmodPfoo() -> f32 {
36 function foo()
37 real(4) :: foo
38 ! CHECK: }
39 end function
40 end module
43 ! CHECK-LABEL: func @_QPfoo2()
44 function foo2()
45 real(4) :: foo2
46 contains
47 ! CHECK-LABEL: func @_QFfoo2Psub() {
48 subroutine sub()
49 ! CHECK: }
50 end subroutine
52 ! CHECK-LABEL: func @_QFfoo2Pfoo() {
53 subroutine foo()
54 ! CHECK: }
55 end subroutine
56 end function
58 ! CHECK-LABEL: func @_QPsub2()
59 subroutine sUb2()
60 contains
61 ! CHECK-LABEL: func @_QFsub2Psub() {
62 subroutine sub()
63 ! CHECK: }
64 end subroutine
66 ! CHECK-LABEL: func @_QFsub2Pfoo() {
67 subroutine Foo()
68 ! CHECK: }
69 end subroutine
70 end subroutine
72 module testMod2
73 contains
74 ! CHECK-LABEL: func @_QMtestmod2Psub()
75 subroutine sub()
76 contains
77 ! CHECK-LABEL: func @_QMtestmod2FsubPsubsub() {
78 subroutine subSub()
79 ! CHECK: }
80 end subroutine
81 end subroutine
82 end module
85 module color_points
86 interface
87 module subroutine draw()
88 end subroutine
89 module function erase()
90 integer(4) :: erase
91 end function
92 end interface
93 end module color_points
95 submodule (color_points) color_points_a
96 contains
97 ! CHECK-LABEL: func @_QMcolor_pointsScolor_points_aPsub() {
98 subroutine sub
99 end subroutine
100 ! CHECK: }
101 end submodule
103 submodule (color_points:color_points_a) impl
104 contains
105 ! CHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplPfoo()
106 subroutine foo
107 contains
108 ! CHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplFfooPbar() {
109 subroutine bar
110 ! CHECK: }
111 end subroutine
112 end subroutine
113 ! CHECK-LABEL: func @_QMcolor_pointsPdraw() {
114 module subroutine draw()
115 end subroutine
116 !FIXME func @_QMcolor_pointsPerase() -> i32 {
117 module procedure erase
118 ! CHECK: }
119 end procedure
120 end submodule
122 ! CHECK-LABEL: func @_QPshould_not_collide() {
123 subroutine should_not_collide()
124 ! CHECK: }
125 end subroutine
127 ! CHECK-LABEL: func @_QQmain() attributes {fir.bindc_name = "test"} {
128 program test
129 ! CHECK: }
130 contains
131 ! CHECK-LABEL: func @_QFPshould_not_collide() {
132 subroutine should_not_collide()
133 ! CHECK: }
134 end subroutine
135 end program
137 ! CHECK-LABEL: func @omp_get_num_threads() -> f32 attributes {fir.bindc_name = "omp_get_num_threads"} {
138 function omp_get_num_threads() bind(c)
139 ! CHECK: }
140 end function
142 ! CHECK-LABEL: func @get_threads() -> f32 attributes {fir.bindc_name = "get_threads"} {
143 function omp_get_num_threads_1() bind(c, name ="get_threads")
144 ! CHECK: }
145 end function
147 ! CHECK-LABEL: func @bEtA() -> f32 attributes {fir.bindc_name = "bEtA"} {
148 function alpha() bind(c, name =" bEtA ")
149 ! CHECK: }
150 end function
152 ! CHECK-LABEL: func @bc1() attributes {fir.bindc_name = "bc1"} {
153 subroutine bind_c_s() Bind(C,Name='bc1')
154 ! CHECK: return
155 end subroutine bind_c_s
157 ! CHECK-LABEL: func @_QPbind_c_s() {
158 subroutine bind_c_s()
159 ! CHECK: fir.call @_QPbind_c_q() {{.*}}: () -> ()
160 ! CHECK: return
161 call bind_c_q
164 ! CHECK-LABEL: func @_QPbind_c_q() {
165 subroutine bind_c_q()
166 interface
167 subroutine bind_c_s() Bind(C, name='bc1')
169 end interface
170 ! CHECK: fir.call @bc1() {{.*}}: () -> ()
171 ! CHECK: return
172 call bind_c_s
175 ! Test that BIND(C) label is taken into account for ENTRY symbols.
176 ! CHECK-LABEL: func @_QPsub_with_entries() {
177 subroutine sub_with_entries
178 ! CHECK-LABEL: func @bar() attributes {fir.bindc_name = "bar"} {
179 entry some_entry() bind(c, name="bar")
180 ! CHECK-LABEL: func @_QPnormal_entry() {
181 entry normal_entry()
182 ! CHECK-LABEL: func @some_other_entry() attributes {fir.bindc_name = "some_other_entry"} {
183 entry some_other_entry() bind(c)
184 end subroutine
186 ! Test that semantics constructs binding labels with local name resolution
187 module testMod3
188 character*(*), parameter :: foo = "bad!!"
189 character*(*), parameter :: ok = "ok"
190 interface
191 real function f1() bind(c,name=ok//'1')
192 import ok
193 end function
194 subroutine s1() bind(c,name=ok//'2')
195 import ok
196 end subroutine
197 end interface
198 contains
199 ! CHECK-LABEL: func @ok3() -> f32 attributes {fir.bindc_name = "ok3"} {
200 real function f2() bind(c,name=foo//'3')
201 character*(*), parameter :: foo = ok
202 ! CHECK: fir.call @ok1() {{.*}}: () -> f32
203 ! CHECK-LABEL: func @ok4() -> f32 attributes {fir.bindc_name = "ok4"} {
204 entry f3() bind(c,name=foo//'4')
205 ! CHECK: fir.call @ok1() {{.*}}: () -> f32
206 f2 = f1()
207 end function
208 ! CHECK-LABEL: func @ok5() attributes {fir.bindc_name = "ok5"} {
209 subroutine s2() bind(c,name=foo//'5')
210 character*(*), parameter :: foo = ok
211 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
212 ! CHECK-LABEL: func @ok6() attributes {fir.bindc_name = "ok6"} {
213 entry s3() bind(c,name=foo//'6')
214 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
215 continue ! force end of specification part
216 ! CHECK-LABEL: func @ok7() attributes {fir.bindc_name = "ok7"} {
217 entry s4() bind(c,name=foo//'7')
218 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
219 call s1
220 end subroutine
221 end module
224 ! CHECK-LABEL: func @_QPnest1
225 subroutine nest1
226 ! CHECK: fir.call @_QFnest1Pinner()
227 call inner
228 contains
229 ! CHECK-LABEL: func @_QFnest1Pinner
230 subroutine inner
231 ! CHECK: %[[V_0:[0-9]+]] = fir.address_of(@_QFnest1FinnerEkk) : !fir.ref<i32>
232 integer, save :: kk = 1
233 print*, 'qq:inner', kk
237 ! CHECK-LABEL: func @_QPnest2
238 subroutine nest2
239 ! CHECK: fir.call @_QFnest2Pinner()
240 call inner
241 contains
242 ! CHECK-LABEL: func @_QFnest2Pinner
243 subroutine inner
244 ! CHECK: %[[V_0:[0-9]+]] = fir.address_of(@_QFnest2FinnerEkk) : !fir.ref<i32>
245 integer, save :: kk = 77
246 print*, 'ss:inner', kk
250 ! CHECK-LABEL: fir.global internal @_QFfooEpi : f32 {