[flang][openacc][NFC] Check only HLFIR lowering for atomic tests (#72922)
[llvm-project.git] / flang / test / Lower / derived-type-temp.f90
blob18bcacf10753c676e66ce3a97d650d42a36a0f79
1 ! Test lowering of derived type temporary creation and init
2 ! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
4 program derived_temp_init
5 type t1
6 integer, allocatable :: i
7 end type
8 type t2
9 type(t1) :: c
10 end type
11 type(t1) :: x
12 type(t2) :: y
13 y = t2(x)
14 end
16 ! CHECK: %[[temp:.*]] = fir.alloca !fir.type<_QFTt1{i:!fir.box<!fir.heap<i32>>}> {bindc_name = "x", uniq_name = "_QFEx"}
17 ! CHECK: %[[box:.*]] = fir.embox %[[temp]] : (!fir.ref<!fir.type<_QFTt1{i:!fir.box<!fir.heap<i32>>}>>) -> !fir.box<!fir.type<_QFTt1{i:!fir.box<!fir.heap<i32>>}>>
18 ! CHECK: %[[box_none:.*]] = fir.convert %[[box]] : (!fir.box<!fir.type<_QFTt1{i:!fir.box<!fir.heap<i32>>}>>) -> !fir.box<none>
19 ! CHECK: %{{.*}} = fir.call @_FortranAInitialize(%[[box_none]], %{{.*}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.ref<i8>, i32) -> none