[Clang] Make OpenMP offloading consistently use the bound architecture (#125135)
[llvm-project.git] / flang / test / Lower / HLFIR / associate-for-args-with-alloc-components.f90
blob0aae9e7b62a7e49d968e568bb0623c47f766e98e
1 ! Test that the hlfir.end_associate generated for the argument
2 ! passing has operand that is a Fortran entity, so that
3 ! the shape/type-params information is available
4 ! during bufferization that will have to generate a runtime call
5 ! for deallocating the allocatable component of the temporary.
7 ! RUN: bbc -emit-hlfir -o - -I nowhere %s | FileCheck %s
9 module types
10 type t
11 real, allocatable :: x
12 end type t
13 contains
14 end module types
16 subroutine test1(x)
17 use types
18 interface
19 subroutine callee1(x)
20 use types
21 type(t), value :: x(10)
22 end subroutine callee1
23 end interface
24 type(t) :: x(:)
25 call callee1(x)
26 end subroutine test1
27 ! CHECK-LABEL: func.func @_QPtest1(
28 ! CHECK: %[[VAL_6:.*]]:3 = hlfir.associate %{{.*}}(%{{.*}}) {adapt.valuebyref} : (!hlfir.expr<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>, !fir.shape<1>) -> (!fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.ref<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1)
29 ! CHECK: hlfir.end_associate %[[VAL_6]]#0, %[[VAL_6]]#2 : !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1
31 subroutine test2(x)
32 use types
33 interface
34 subroutine callee2(x)
35 use types
36 type(t) :: x(:)
37 end subroutine callee2
38 end interface
39 type(t) :: x(:)
40 call callee2((x))
41 end subroutine test2
42 ! CHECK-LABEL: func.func @_QPtest2(
43 ! CHECK: %[[VAL_9:.*]]:3 = hlfir.associate %{{.*}}(%{{.*}}) {adapt.valuebyref} : (!hlfir.expr<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>, !fir.shape<1>) -> (!fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.ref<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1)
44 ! CHECK: hlfir.end_associate %[[VAL_9]]#0, %[[VAL_9]]#2 : !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1
46 subroutine test3(x)
47 use types
48 interface
49 subroutine callee3(x)
50 use types
51 type(t), optional, value :: x(10)
52 end subroutine callee3
53 end interface
54 type(t), optional :: x(:)
55 call callee3(x)
56 end subroutine test3
57 ! CHECK-LABEL: func.func @_QPtest3(
58 ! CHECK: %[[VAL_3:.*]]:3 = fir.if %{{.*}} -> (!fir.ref<!fir.array<10x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1) {
59 ! CHECK: %[[VAL_8:.*]]:3 = hlfir.associate %{{.*}}(%{{.*}}) {adapt.valuebyref} : (!hlfir.expr<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>, !fir.shape<1>) -> (!fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.ref<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1)
60 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_8]]#1 : (!fir.ref<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>) -> !fir.ref<!fir.array<10x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>
61 ! CHECK: fir.result %[[VAL_9]], %[[VAL_8]]#0, %[[VAL_8]]#2 : !fir.ref<!fir.array<10x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1
62 ! CHECK: } else {
63 ! CHECK: fir.result %{{.*}}, %{{.*}}, %{{.*}} : !fir.ref<!fir.array<10x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1
64 ! CHECK: }
65 ! CHECK: hlfir.end_associate %[[VAL_3]]#1, %[[VAL_3]]#2 : !fir.box<!fir.array<?x!fir.type<_QMtypesTt{x:!fir.box<!fir.heap<f32>>}>>>, i1