1 ! Test for PassBy::Value
2 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
4 !CHECK-LABEL: func @_QQmain()
5 !CHECK: %[[LOGICAL:.*]] = fir.alloca !fir.logical<4>
6 !CHECK: %false = arith.constant false
7 !CHECK: %[[VALUE:.*]] = fir.convert %false : (i1) -> !fir.logical<4>
8 !CHECK: fir.store %[[VALUE]] to %[[LOGICAL]]
9 !CHECK: %[[LOAD:.*]] = fir.load %[[LOGICAL]]
10 !CHECK: fir.call @omp_set_nested(%[[LOAD]]) {{.*}}: {{.*}}
14 subroutine omp_set_nested(enable
) bind(c
)
15 logical, value
:: enable
16 end subroutine omp_set_nested
21 call omp_set_nested(do_nested
)
22 end program call_by_value
24 ! CHECK-LABEL: func.func @test_integer_value(
25 ! CHECK-SAME: %[[VAL_0:.*]]: i32 {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_integer_value"} {
26 ! CHECK: %[[VAL_1:.*]] = fir.alloca i32
27 ! CHECK: fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<i32>
28 ! CHECK: fir.call @_QPinternal_call(%[[VAL_1]]) {{.*}}: (!fir.ref<i32>) -> ()
32 subroutine test_integer_value(x
) bind(c
)
37 ! CHECK-LABEL: func.func @test_real_value(
38 ! CHECK-SAME: %[[VAL_0:.*]]: f32 {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_real_value"} {
39 ! CHECK: %[[VAL_1:.*]] = fir.alloca f32
40 ! CHECK: fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<f32>
41 ! CHECK: fir.call @_QPinternal_call2(%[[VAL_1]]) {{.*}}: (!fir.ref<f32>) -> ()
45 subroutine test_real_value(x
) bind(c
)
47 call internal_call2(x
)
50 ! CHECK-LABEL: func.func @test_complex_value(
51 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.complex<4> {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_complex_value"} {
52 ! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.complex<4>
53 ! CHECK: fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<!fir.complex<4>>
54 ! CHECK: fir.call @_QPinternal_call3(%[[VAL_1]]) {{.*}}: (!fir.ref<!fir.complex<4>>) -> ()
58 subroutine test_complex_value(x
) bind(c
)
60 call internal_call3(x
)
63 ! CHECK-LABEL: func.func @test_char_value(
64 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.boxchar<1> {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_char_value"} {
65 ! CHECK: %[[VAL_1:.*]]:2 = fir.unboxchar %[[VAL_0]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
66 ! CHECK: %[[VAL_2:.*]] = arith.constant 1 : index
67 ! CHECK: %[[VAL_3:.*]] = fir.emboxchar %[[VAL_1]]#0, %[[VAL_2]] : (!fir.ref<!fir.char<1,?>>, index) -> !fir.boxchar<1>
68 ! CHECK: fir.call @_QPinternal_call4(%[[VAL_3]]) {{.*}}: (!fir.boxchar<1>) -> ()
72 subroutine test_char_value(x
) bind(c
)
73 character(1), value
:: x
74 call internal_call4(x
)
77 ! CHECK-LABEL: func.func @_QPtest_cptr_value(
78 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<i64> {fir.bindc_name = "x"}) {
79 ! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>
80 ! CHECK: %[[VAL_2:.*]] = fir.field_index __address, !fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>
81 ! CHECK: %[[VAL_3:.*]] = fir.coordinate_of %[[VAL_1]], %[[VAL_2]] : (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>, !fir.field) -> !fir.ref<i64>
82 ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<i64>) -> i64
83 ! CHECK: fir.store %[[VAL_4]] to %[[VAL_3]] : !fir.ref<i64>
84 ! CHECK: fir.call @_QPinternal_call5(%[[VAL_1]]) {{.*}}: (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>) -> ()
88 subroutine test_cptr_value(x
)
90 type(c_ptr
), value
:: x
91 call internal_call5(x
)