Fix warnings occured during profiledboostrap on
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_allocate_17.f90
blob639ba80ea60f07f2d0a306f78a50ca4fe8b22054
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! PR 60922: [4.9/5 regression] Memory leak with allocatable CLASS components
6 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
8 program test_leak
9 implicit none
11 type d_base_vect_type
12 end type
14 type d_vect_type
15 class(d_base_vect_type), allocatable :: v
16 end type
18 call test()
20 contains
22 subroutine test()
23 class(d_vect_type), allocatable :: x
24 allocate(x)
25 allocate(x%v)
26 print *,"allocated!"
27 end subroutine
29 end
31 ! { dg-final { scan-tree-dump-times "fini_coarray" 1 "original" } }
32 ! { dg-final { cleanup-tree-dump "original" } }