[Clang] Make OpenMP offloading consistently use the bound architecture (#125135)
[llvm-project.git] / flang / test / Lower / HLFIR / elemental-call-with-finalization.f90
blob181c6b74e91096e670e1cb72eac29691e18a1da6
1 ! Test HLFIR lowering of user defined elemental procedure references
2 ! with finalizable results. Verify that the elemental results
3 ! are not destroyed inside hlfir.elemental.
4 ! RUN: bbc -emit-hlfir -o - -I nowhere %s 2>&1 | FileCheck %s
6 module types
7 type t
8 contains
9 final :: finalize
10 end type t
11 contains
12 pure subroutine finalize(x)
13 type(t), intent(inout) :: x
14 end subroutine finalize
15 end module types
17 subroutine test1(x)
18 use types
19 interface
20 elemental function elem(x)
21 use types
22 type(t), intent(in) :: x
23 type(t) :: elem
24 end function elem
25 end interface
26 type(t) :: x(:)
27 x = elem(x)
28 end subroutine test1
29 ! CHECK-LABEL: func.func @_QPtest1(
30 ! CHECK: %[[VAL_6:.*]] = hlfir.elemental %{{.*}} : (!fir.shape<1>) -> !hlfir.expr<?x!fir.type<_QMtypesTt>> {
31 ! CHECK-NOT: fir.call @_FortranADestroy
32 ! CHECK: hlfir.destroy %[[VAL_6]] finalize : !hlfir.expr<?x!fir.type<_QMtypesTt>>
34 subroutine test2(x)
35 use types
36 interface
37 elemental function elem(x)
38 use types
39 type(t), intent(in) :: x
40 type(t) :: elem
41 end function elem
42 elemental function elem2(x, y)
43 use types
44 type(t), intent(in) :: x, y
45 type(t) :: elem2
46 end function elem2
47 end interface
48 type(t) :: x(:)
49 x = elem2(elem(x), elem(x))
50 end subroutine test2
51 ! CHECK-LABEL: func.func @_QPtest2(
52 ! CHECK: %[[VAL_8:.*]] = hlfir.elemental %{{.*}} : (!fir.shape<1>) -> !hlfir.expr<?x!fir.type<_QMtypesTt>> {
53 ! CHECK-NOT: fir.call @_FortranADestroy
54 ! CHECK: %[[VAL_16:.*]] = hlfir.elemental %{{.*}} : (!fir.shape<1>) -> !hlfir.expr<?x!fir.type<_QMtypesTt>> {
55 ! CHECK-NOT: fir.call @_FortranADestroy
56 ! CHECK: %[[VAL_23:.*]] = hlfir.elemental %{{.*}} : (!fir.shape<1>) -> !hlfir.expr<?x!fir.type<_QMtypesTt>> {
57 ! CHECK-NOT: fir.call @_FortranADestroy
58 ! CHECK: hlfir.destroy %[[VAL_23]] finalize : !hlfir.expr<?x!fir.type<_QMtypesTt>>
59 ! CHECK: hlfir.destroy %[[VAL_16]] finalize : !hlfir.expr<?x!fir.type<_QMtypesTt>>
60 ! CHECK: hlfir.destroy %[[VAL_8]] finalize : !hlfir.expr<?x!fir.type<_QMtypesTt>>