[Support] Recycler: Implement move constructor (#120555)
[llvm-project.git] / flang / test / HLFIR / call_with_poly_dummy.f90
blob93cd410428f7b4c565ebbd598bb239a282dfa655
1 ! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
3 ! Test passing arguments to subprograms with polymorphic dummy arguments.
5 ! CHECK-LABEL: func.func @_QPtest1() {
6 ! CHECK: %[[VAL_0:.*]] = arith.constant 17 : i32
7 ! CHECK: %[[VAL_1:.*]]:3 = hlfir.associate %[[VAL_0]] {adapt.valuebyref} : (i32) -> (!fir.ref<i32>, !fir.ref<i32>, i1)
8 ! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]]#0 : (!fir.ref<i32>) -> !fir.box<i32>
9 ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.box<i32>) -> !fir.class<none>
10 ! CHECK: fir.call @_QPcallee(%[[VAL_3]]) fastmath<contract> : (!fir.class<none>) -> ()
11 ! CHECK: hlfir.end_associate %[[VAL_1]]#1, %[[VAL_1]]#2 : !fir.ref<i32>, i1
12 ! CHECK: return
13 ! CHECK: }
14 subroutine test1
15 interface
16 subroutine callee(x)
17 class(*) x
18 end subroutine callee
19 end interface
20 call callee(17)
21 end subroutine test1
23 ! CHECK-LABEL: func.func @_QPtest2(
24 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<f32> {fir.bindc_name = "x"}) {
25 ! CHECK: %[[DSCOPE:.*]] = fir.dummy_scope : !fir.dscope
26 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[DSCOPE]] {uniq_name = "_QFtest2Ex"} : (!fir.ref<f32>, !fir.dscope) -> (!fir.ref<f32>, !fir.ref<f32>)
27 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<f32>
28 ! CHECK: %[[VAL_3:.*]] = arith.constant 0.000000e+00 : f32
29 ! CHECK: %[[VAL_4:.*]] = arith.cmpf oeq, %[[VAL_2]], %[[VAL_3]] {{.*}} : f32
30 ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (i1) -> !fir.logical<4>
31 ! CHECK: %[[VAL_6:.*]]:3 = hlfir.associate %[[VAL_5]] {adapt.valuebyref} : (!fir.logical<4>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>, i1)
32 ! CHECK: %[[VAL_7:.*]] = fir.embox %[[VAL_6]]#0 : (!fir.ref<!fir.logical<4>>) -> !fir.box<!fir.logical<4>>
33 ! CHECK: %[[VAL_8:.*]] = fir.rebox %[[VAL_7]] : (!fir.box<!fir.logical<4>>) -> !fir.class<none>
34 ! CHECK: fir.call @_QPcallee(%[[VAL_8]]) fastmath<contract> : (!fir.class<none>) -> ()
35 ! CHECK: hlfir.end_associate %[[VAL_6]]#1, %[[VAL_6]]#2 : !fir.ref<!fir.logical<4>>, i1
36 ! CHECK: return
37 ! CHECK: }
38 subroutine test2(x)
39 interface
40 subroutine callee(x)
41 class(*) x
42 end subroutine callee
43 end interface
44 call callee(x.eq.0)
45 end subroutine test2