OSDN Git Service

2010-06-07 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / auto_dealloc_1.f90
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
3 !
4 ! PR 41586: Allocatable _scalars_ are never auto-deallocated
5 !
6 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
7
8 module automatic_deallocation
9
10   type t0
11     integer :: i
12   end type
13
14   type t1
15     real :: pi = 3.14
16     integer, allocatable :: j
17   end type
18
19   type t2
20     class(t0), allocatable :: k
21   end type t2
22
23 contains
24
25   ! (1) simple allocatable scalars
26   subroutine a
27     integer, allocatable :: m
28     allocate (m)
29     m = 42
30   end subroutine
31
32   ! (2) allocatable scalar CLASS variables
33   subroutine b
34     class(t0), allocatable :: m
35     allocate (t0 :: m)
36     m%i = 43
37   end subroutine
38
39   ! (3) allocatable scalar components
40   subroutine c
41     type(t1) :: m
42     allocate (m%j)
43     m%j = 44
44   end subroutine
45
46   ! (4) allocatable scalar CLASS components
47   subroutine d
48     type(t2) :: m
49     allocate (t0 :: m%k)
50     m%k%i = 45
51   end subroutine
52
53 end module 
54
55
56 ! { dg-final { scan-tree-dump-times "__builtin_free" 4 "original" } }
57
58 ! { dg-final { cleanup-modules "automatic_deallocation" } }
59 ! { dg-final { cleanup-tree-dump "original" } }