[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Lower / program-units-fir-mangling.f90
blob348849fb829ba1de092e1f465263e5cb52aac20c
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 ! We don't handle lowering of submodules yet. The following tests are
96 ! commented out and "CHECK" is changed to "xHECK" to not trigger FileCheck.
97 !submodule (color_points) color_points_a
98 !contains
99 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aPsub() {
100 ! subroutine sub
101 ! end subroutine
102 ! ! xHECK: }
103 !end submodule
105 !submodule (color_points:color_points_a) impl
106 !contains
107 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplPfoo()
108 ! subroutine foo
109 ! contains
110 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplFfooPbar() {
111 ! subroutine bar
112 ! ! xHECK: }
113 ! end subroutine
114 ! end subroutine
115 ! ! xHECK-LABEL: func @_QMcolor_pointsPdraw() {
116 ! module subroutine draw()
117 ! end subroutine
118 ! !FIXME func @_QMcolor_pointsPerase() -> i32 {
119 ! module procedure erase
120 ! ! xHECK: }
121 ! end procedure
122 !end submodule
124 ! CHECK-LABEL: func @_QPshould_not_collide() {
125 subroutine should_not_collide()
126 ! CHECK: }
127 end subroutine
129 ! CHECK-LABEL: func @_QQmain() attributes {fir.bindc_name = "test"} {
130 program test
131 ! CHECK: }
132 contains
133 ! CHECK-LABEL: func @_QFPshould_not_collide() {
134 subroutine should_not_collide()
135 ! CHECK: }
136 end subroutine
137 end program
139 ! CHECK-LABEL: func @omp_get_num_threads() -> f32 attributes {fir.bindc_name = "omp_get_num_threads"} {
140 function omp_get_num_threads() bind(c)
141 ! CHECK: }
142 end function
144 ! CHECK-LABEL: func @get_threads() -> f32 attributes {fir.bindc_name = "get_threads"} {
145 function omp_get_num_threads_1() bind(c, name ="get_threads")
146 ! CHECK: }
147 end function
149 ! CHECK-LABEL: func @bEtA() -> f32 attributes {fir.bindc_name = "bEtA"} {
150 function alpha() bind(c, name =" bEtA ")
151 ! CHECK: }
152 end function
154 ! CHECK-LABEL: func @bc1() attributes {fir.bindc_name = "bc1"} {
155 subroutine bind_c_s() Bind(C,Name='bc1')
156 ! CHECK: return
157 end subroutine bind_c_s
159 ! CHECK-LABEL: func @_QPbind_c_s() {
160 subroutine bind_c_s()
161 ! CHECK: fir.call @_QPbind_c_q() {{.*}}: () -> ()
162 ! CHECK: return
163 call bind_c_q
166 ! CHECK-LABEL: func @_QPbind_c_q() {
167 subroutine bind_c_q()
168 interface
169 subroutine bind_c_s() Bind(C, name='bc1')
171 end interface
172 ! CHECK: fir.call @bc1() {{.*}}: () -> ()
173 ! CHECK: return
174 call bind_c_s
177 ! Test that BIND(C) label is taken into account for ENTRY symbols.
178 ! CHECK-LABEL: func @_QPsub_with_entries() {
179 subroutine sub_with_entries
180 ! CHECK-LABEL: func @bar() attributes {fir.bindc_name = "bar"} {
181 entry some_entry() bind(c, name="bar")
182 ! CHECK-LABEL: func @_QPnormal_entry() {
183 entry normal_entry()
184 ! CHECK-LABEL: func @some_other_entry() attributes {fir.bindc_name = "some_other_entry"} {
185 entry some_other_entry() bind(c)
186 end subroutine
188 ! Test that semantics constructs binding labels with local name resolution
189 module testMod3
190 character*(*), parameter :: foo = "bad!!"
191 character*(*), parameter :: ok = "ok"
192 interface
193 real function f1() bind(c,name=ok//'1')
194 import ok
195 end function
196 subroutine s1() bind(c,name=ok//'2')
197 import ok
198 end subroutine
199 end interface
200 contains
201 ! CHECK-LABEL: func @ok3() -> f32 attributes {fir.bindc_name = "ok3"} {
202 real function f2() bind(c,name=foo//'3')
203 character*(*), parameter :: foo = ok
204 ! CHECK: fir.call @ok1() {{.*}}: () -> f32
205 ! CHECK-LABEL: func @ok4() -> f32 attributes {fir.bindc_name = "ok4"} {
206 entry f3() bind(c,name=foo//'4')
207 ! CHECK: fir.call @ok1() {{.*}}: () -> f32
208 f2 = f1()
209 end function
210 ! CHECK-LABEL: func @ok5() attributes {fir.bindc_name = "ok5"} {
211 subroutine s2() bind(c,name=foo//'5')
212 character*(*), parameter :: foo = ok
213 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
214 ! CHECK-LABEL: func @ok6() attributes {fir.bindc_name = "ok6"} {
215 entry s3() bind(c,name=foo//'6')
216 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
217 continue ! force end of specification part
218 ! CHECK-LABEL: func @ok7() attributes {fir.bindc_name = "ok7"} {
219 entry s4() bind(c,name=foo//'7')
220 ! CHECK: fir.call @ok2() {{.*}}: () -> ()
221 call s1
222 end subroutine
223 end module
225 ! CHECK-LABEL: fir.global internal @_QFfooEpi : f32 {