aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/move_alloc_14.f90
blob: bc5e491651292424898477a3ff99232e97ad0f42 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
! { dg-do run }
!
! Ensure that move_alloc for CLASS resets the FROM variable's dynamic type
! to the declared one
!
implicit none
type t
end type t
type, extends(t) :: t2
end type t2

class(t), allocatable :: a, b, c
class(t), allocatable :: a2(:), b2(:), c2(:)
allocate (t2 :: a)
allocate (t2 :: a2(5))
call move_alloc (from=a, to=b)
call move_alloc (from=a2, to=b2)
!print *, same_type_as (a,c), same_type_as (a,b)
!print *, same_type_as (a2,c2), same_type_as (a2,b2)
if (.not. same_type_as (a,c) .or. same_type_as (a,b)) call abort ()
if (.not. same_type_as (a2,c2) .or. same_type_as (a2,b2)) call abort ()
end