! Test lowering of derived types passed with VALUE attribute in BIND(C) ! interface. They are passed as fir.type value. The actual C struct ! passing ABI is done in code generation according to the target. ! RUN: bbc -emit-hlfir -o - -I nw %s 2>&1 | FileCheck %s module bindc_byval type, bind(c) :: t integer :: i end type contains subroutine test(x) bind(c) type(t), value :: x call use_it(x%i) end subroutine ! CHECK-LABEL: func.func @test( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.type<_QMbindc_byvalTt{i:i32}> {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test"} { ! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.type<_QMbindc_byvalTt{i:i32}> ! CHECK: fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref> ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QMbindc_byvalFtestEx"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[VAL_3:.*]] = hlfir.designate %[[VAL_2]]#0{"i"} : (!fir.ref>) -> !fir.ref ! CHECK: fir.call @_QPuse_it(%[[VAL_3]]) fastmath : (!fir.ref) -> () ! CHECK: return ! CHECK: } subroutine call_it(x) type(t) x call test(x) end subroutine ! CHECK-LABEL: func.func @_QMbindc_byvalPcall_it( ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref> {fir.bindc_name = "x"}) { ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QMbindc_byvalFcall_itEx"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#1 : !fir.ref> ! CHECK: fir.call @test(%[[VAL_2]]) fastmath : (!fir.type<_QMbindc_byvalTt{i:i32}>) -> () ! CHECK: return ! CHECK: } end module