xref: /llvm-project/flang/test/Lower/HLFIR/function-return-destroy.f90 (revision d0829fbdeda0a2faa8cf684e1396e579691bdfa2)
1! RUN: bbc -emit-hlfir %s -o - -I nowhere | FileCheck %s
2
3module types
4  type t1
5     real :: x
6  end type t1
7  type t2
8     real, allocatable :: x
9  end type t2
10  type t3
11     real, pointer :: p
12  end type t3
13  type t4
14     type(t1) :: c
15  end type t4
16  type t5
17     type(t2) :: c
18  end type t5
19  type t6
20   contains
21     final :: finalize_t6
22  end type t6
23  type, extends(t1) :: t7
24  end type t7
25  type, extends(t2) :: t8
26  end type t8
27  type, extends(t6) :: t9
28  end type t9
29contains
30  subroutine finalize_t6(x)
31    type(t6), intent(inout) :: x
32  end subroutine finalize_t6
33end module types
34
35subroutine test1
36  use types
37  interface
38     function ret_type_t1
39       use types
40       type(t1) :: ret_type_t1
41     end function ret_type_t1
42  end interface
43  type(t1) :: x
44  x = ret_type_t1()
45end subroutine test1
46! CHECK-LABEL:   func.func @_QPtest1() {
47! CHECK-NOT: fir.call{{.*}}Destroy
48
49subroutine test1a
50  use types
51  interface
52     function ret_type_t1a
53       use types
54       type(t1), allocatable :: ret_type_t1a
55     end function ret_type_t1a
56  end interface
57  type(t1), allocatable :: x
58  x = ret_type_t1a()
59end subroutine test1a
60! CHECK-LABEL:   func.func @_QPtest1a() {
61! CHECK-NOT: fir.call{{.*}}Destroy
62! CHECK:           fir.if %{{.*}} {
63! CHECK-NEXT:        fir.freemem %{{.*}} : !fir.heap<!fir.type<_QMtypesTt1{x:f32}>>
64! CHECK-NOT: fir.call{{.*}}Destroy
65! CHECK:           fir.if %{{.*}} {
66! CHECK:             fir.call @_FortranAAllocatableDeallocate({{.*}}) fastmath<contract> : (!fir.ref<!fir.box<none>>, i1, !fir.box<none>, !fir.ref<i8>, i32) -> i32
67! CHECK-NOT: fir.call{{.*}}Destroy
68
69subroutine test1c
70  use types
71  interface
72     function ret_class_t1
73       use types
74       class(t1), allocatable :: ret_class_t1
75     end function ret_class_t1
76  end interface
77  type(t1) :: x
78  x = ret_class_t1()
79end subroutine test1c
80! CHECK-LABEL:   func.func @_QPtest1c() {
81! CHECK: fir.call @_FortranADestroy
82! CHECK:           fir.if %{{.*}} {
83! CHECK-NEXT:        fir.freemem %{{.*}} : !fir.heap<!fir.type<_QMtypesTt1{x:f32}>>
84
85subroutine test2
86  use types
87  interface
88     function ret_type_t2
89       use types
90       type(t2) :: ret_type_t2
91     end function ret_type_t2
92  end interface
93  type(t2) :: x
94  x = ret_type_t2()
95end subroutine test2
96! CHECK-LABEL:   func.func @_QPtest2() {
97! CHECK: fir.call @_FortranADestroy
98
99subroutine test3
100  use types
101  interface
102     function ret_type_t3
103       use types
104       type(t3) :: ret_type_t3
105     end function ret_type_t3
106  end interface
107  type(t3) :: x
108  x = ret_type_t3()
109end subroutine test3
110! CHECK-LABEL:   func.func @_QPtest3() {
111! CHECK-NOT: fir.call{{.*}}Destroy
112
113subroutine test4
114  use types
115  interface
116     function ret_type_t4
117       use types
118       type(t4) :: ret_type_t4
119     end function ret_type_t4
120  end interface
121  type(t4) :: x
122  x = ret_type_t4()
123end subroutine test4
124! CHECK-LABEL:   func.func @_QPtest4() {
125! CHECK-NOT: fir.call{{.*}}Destroy
126
127subroutine test5
128  use types
129  interface
130     function ret_type_t5
131       use types
132       type(t5) :: ret_type_t5
133     end function ret_type_t5
134  end interface
135  type(t5) :: x
136  x = ret_type_t5()
137end subroutine test5
138! CHECK-LABEL:   func.func @_QPtest5() {
139! CHECK: fir.call @_FortranADestroy
140
141subroutine test6
142  use types
143  interface
144     function ret_type_t6
145       use types
146       type(t6) :: ret_type_t6
147     end function ret_type_t6
148  end interface
149  type(t6) :: x
150  x = ret_type_t6()
151end subroutine test6
152! CHECK-LABEL:   func.func @_QPtest6() {
153! CHECK: fir.call @_FortranADestroy
154! CHECK: fir.call @_FortranADestroy
155
156subroutine test7
157  use types
158  interface
159     function ret_type_t7
160       use types
161       type(t7) :: ret_type_t7
162     end function ret_type_t7
163  end interface
164  type(t7) :: x
165  x = ret_type_t7()
166end subroutine test7
167! CHECK-LABEL:   func.func @_QPtest7() {
168! CHECK-NOT: fir.call{{.*}}Destroy
169
170subroutine test8
171  use types
172  interface
173     function ret_type_t8
174       use types
175       type(t8) :: ret_type_t8
176     end function ret_type_t8
177  end interface
178  type(t8) :: x
179  x = ret_type_t8()
180end subroutine test8
181! CHECK-LABEL:   func.func @_QPtest8() {
182! CHECK: fir.call @_FortranADestroy
183
184subroutine test9
185  use types
186  interface
187     function ret_type_t9
188       use types
189       type(t9) :: ret_type_t9
190     end function ret_type_t9
191  end interface
192  type(t9) :: x
193  x = ret_type_t9()
194end subroutine test9
195! CHECK-LABEL:   func.func @_QPtest9() {
196! CHECK: fir.call @_FortranADestroy
197! CHECK: fir.call @_FortranADestroy
198