1 ! RUN: bbc %s -o "-" -emit-fir | FileCheck %s
3 ! CHECK-LABEL: func @_QPsub() {
8 ! CHECK-LABEL: func @_QPasubroutine() {
9 subroutine AsUbRoUtInE()
13 ! CHECK-LABEL: func @_QPfoo() -> f32 {
21 ! CHECK-LABEL: func @_QPfunctn() -> f32 {
23 real, parameter :: pi
= 3.14
30 ! CHECK-LABEL: func @_QMtestmodPsub() {
35 ! CHECK-LABEL: func @_QMtestmodPfoo() -> f32 {
43 ! CHECK-LABEL: func @_QPfoo2()
47 ! CHECK-LABEL: func @_QFfoo2Psub() {
52 ! CHECK-LABEL: func @_QFfoo2Pfoo() {
58 ! CHECK-LABEL: func @_QPsub2()
61 ! CHECK-LABEL: func @_QFsub2Psub() {
66 ! CHECK-LABEL: func @_QFsub2Pfoo() {
74 ! CHECK-LABEL: func @_QMtestmod2Psub()
77 ! CHECK-LABEL: func @_QMtestmod2FsubPsubsub() {
87 module subroutine draw()
89 module function erase()
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
99 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aPsub() {
105 !submodule (color_points:color_points_a) impl
107 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplPfoo()
110 ! ! xHECK-LABEL: func @_QMcolor_pointsScolor_points_aSimplFfooPbar() {
115 ! ! xHECK-LABEL: func @_QMcolor_pointsPdraw() {
116 ! module subroutine draw()
118 ! !FIXME func @_QMcolor_pointsPerase() -> i32 {
119 ! module procedure erase
124 ! CHECK-LABEL: func @_QPshould_not_collide() {
125 subroutine should_not_collide()
129 ! CHECK-LABEL: func @_QQmain() attributes {fir.bindc_name = "test"} {
133 ! CHECK-LABEL: func @_QFPshould_not_collide() {
134 subroutine should_not_collide()
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
)
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")
149 ! CHECK-LABEL: func @bEtA() -> f32 attributes {fir.bindc_name = "bEtA"} {
150 function alpha() bind(c
, name
=" bEtA ")
154 ! CHECK-LABEL: func @bc1() attributes {fir.bindc_name = "bc1"} {
155 subroutine bind_c_s() Bind(C
,Name
='bc1')
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() {{.*}}: () -> ()
166 ! CHECK-LABEL: func @_QPbind_c_q() {
167 subroutine bind_c_q()
169 subroutine bind_c_s() Bind(C
, name
='bc1')
172 ! CHECK: fir.call @bc1() {{.*}}: () -> ()
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() {
184 ! CHECK-LABEL: func @some_other_entry() attributes {fir.bindc_name = "some_other_entry"} {
185 entry some_other_entry() bind(c
)
188 ! Test that semantics constructs binding labels with local name resolution
190 character*(*), parameter :: foo
= "bad!!"
191 character*(*), parameter :: ok
= "ok"
193 real function f1() bind(c
,name
=ok
//'1')
196 subroutine s1() bind(c
,name
=ok
//'2')
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
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() {{.*}}: () -> ()
225 ! CHECK-LABEL: fir.global internal @_QFfooEpi : f32 {