RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocate_with_source_25.f90
blob92dc50756d4946554c0b0b9f964a32e5a3339278
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! Test the fix for PR86481
6 ! Contributed by Rich Townsend <townsend@astro.wisc.edu>
8 program simple_leak
10 implicit none
12 type, abstract :: foo_t
13 end type foo_t
15 type, extends(foo_t) :: foo_a_t
16 real(8), allocatable :: a(:)
17 end type foo_a_t
19 type, extends(foo_t) :: bar_t
20 class(foo_t), allocatable :: f
21 end type bar_t
23 integer, parameter :: N = 2
24 integer, parameter :: D = 3
26 type(bar_t) :: b(N)
27 integer :: i
29 do i = 1, N
30 b(i) = func_bar(D)
31 end do
33 do i = 1, N
34 deallocate (b(i)%f)
35 end do
37 contains
39 function func_bar (D) result (b)
41 integer, intent(in) :: D
42 type(bar_t) :: b
44 allocate(b%f, SOURCE=func_foo(D))
46 end function func_bar
48 !****
50 function func_foo (D) result (f)
52 integer, intent(in) :: D
53 class(foo_t), allocatable :: f
55 allocate(f, SOURCE=func_foo_a(D)) ! Lose one of these for each allocation
57 end function func_foo
59 !****
61 function func_foo_a (D) result (f)
63 integer, intent(in) :: D
64 type(foo_a_t) :: f
66 allocate(f%a(D)) ! Lose one of these for each allocation => N*D*elem_size(f%a)
68 end function func_foo_a
70 end program simple_leak
71 ! { dg-final { scan-tree-dump-times "\>_final" 6 "original" } }