PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / move_alloc_13.f90
blobc07dc89c44f627cf976f328e16617ce26d7406d9
1 ! { dg-do run }
3 ! PR fortran/51970
4 ! PR fortran/51977
6 type t
7 end type t
8 type, extends(t) :: t2
9 integer :: a
10 end type t2
12 class(t), allocatable :: y(:), z(:)
14 allocate(y(2), source=[t2(2), t2(3)])
15 call func2(y,z)
17 select type(z)
18 type is(t2)
19 if (any (z(:)%a /= [2, 3])) STOP 1
20 class default
21 STOP 2
22 end select
24 contains
25 function func(x)
26 class (t), allocatable :: x(:), func(:)
27 call move_alloc (x, func)
28 end function
30 function func1(x)
31 class (t), allocatable :: x(:), func1(:)
32 call move_alloc (func1, x)
33 end function
35 subroutine func2(x, y)
36 class (t), allocatable :: x(:), y(:)
37 call move_alloc (x, y)
38 end subroutine
39 end