2017-02-20 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_allocate_15.f90
blobd0e85a2a9bab8dc14b755babc8ec0e976dc3e602
1 ! { dg-do run }
2 ! { dg-options "-fdump-tree-original -fdump-tree-original -fmax-stack-var-size=1" }
4 ! PR fortran/56845
6 type t
7 end type t
8 type, extends(t) :: t2
9 end type t2
10 type(t) :: y
11 call foo()
12 call bar()
13 contains
14 subroutine foo()
15 class(t), allocatable :: x
16 if(allocated(x)) call abort()
17 if(.not.same_type_as(x,y)) call abort()
18 allocate (t2 :: x)
19 end
20 subroutine bar()
21 class(t), allocatable :: x(:)
22 if(allocated(x)) call abort()
23 if(.not.same_type_as(x,y)) call abort()
24 allocate (t2 :: x(4))
25 end
26 end
27 ! { dg-final { scan-tree-dump-times "__builtin_free" 2 "original" } }