2 ! { dg-options "-O2 -fdump-tree-original" }
3 ! Test ALLOCATABLE functions; the primary purpose here is to check that
4 ! each of the various types of reference result in the function result
5 ! being deallocated, using _gfortran_internal_free.
6 ! The companion, allocatable_function_1r.f90, executes this program.
9 integer, intent(in
) :: a(:)
11 if (.not
.all(a
== [ 1, 2, 3 ])) call abort()
15 integer, intent(in
) :: n
16 integer, allocatable
:: foo2(:)
27 integer, intent(in
) :: n
28 integer, allocatable
:: foo3(:)
46 integer, intent(in
) :: a(:)
52 integer, intent(in
) :: n
53 integer, allocatable
:: foo2(:)
57 ! 2 _gfortran_internal_free's
58 if (.not
.all(foo1(3) == [ 1, 2, 3 ])) call abort()
61 ! 1 _gfortran_internal_free
62 if (.not
.all(a
== [ 1, 2, 3 ])) call abort()
65 ! 1 _gfortran_internal_free
66 if (.not
.all(2*bar(size(a
)) + 5 == [ 7, 9, 11 ])) call abort()
68 ! Although the rhs determines the loop size, the lhs reference is
69 ! evaluated, in case it has side-effects or is needed for bounds checking.
70 ! 3 _gfortran_internal_free's
71 a(1:size (bar (3))) = 2*bar(size(a
)) + 2 + a(size (bar (3)))
72 if (.not
.all(a
== [ 7, 9, 11 ])) call abort()
74 ! 3 _gfortran_internal_free's
75 call moobar(foo1(3)) ! internal function
76 call moobar(foo2(3)) ! module function
77 call moobar(foo3(3)) ! explicit interface
79 ! 9 _gfortran_internal_free's in total
83 integer, intent(in
) :: a(:)
85 if (.not
.all(a
== [ 1, 2, 3 ])) call abort()
89 integer, intent(in
) :: n
90 integer, allocatable
:: foo1(:)
98 function bar (n
) result(b
)
99 integer, intent(in
) :: n
100 integer, target
, allocatable
:: b(:)
109 end program alloc_fun
110 ! { dg-final { scan-tree-dump-times "free" 10 "original" } }
111 ! { dg-final { cleanup-tree-dump "original" } }