OSDN Git Service

2012-01-27 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / move_alloc_13.f90
1 ! { dg-do run}
2 !
3 ! PR fortran/51970
4 ! PR fortran/51977
5 !
6 type t
7 end type t
8 type, extends(t) :: t2
9   integer :: a
10 end type t2
11
12 class(t), allocatable :: y(:), z(:)
13
14 allocate(y(2), source=[t2(2), t2(3)])
15 call func2(y,z)
16
17 select type(z)
18   type is(t2)
19     if (any (z(:)%a /= [2, 3])) call abort()
20   class default
21     call abort()
22 end select
23
24 contains
25   function func(x)
26    class (t), allocatable :: x(:), func(:)
27    call move_alloc (x, func)
28   end function
29
30   function func1(x)
31    class (t), allocatable :: x(:), func1(:)
32    call move_alloc (func1, x)
33   end function
34
35   subroutine func2(x, y)
36    class (t), allocatable :: x(:), y(:)
37    call move_alloc (x, y)
38   end subroutine
39 end