aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / move_alloc_14.f90
blob71cb086b49a586ad715df5f2fcb2279804387b8f
1 ! { dg-do run }
3 ! Ensure that move_alloc for CLASS resets the FROM variable's dynamic type
4 ! to the declared one
6 implicit none
7 type t
8 end type t
9 type, extends(t) :: t2
10 end type t2
12 class(t), allocatable :: a, b, c
13 class(t), allocatable :: a2(:), b2(:), c2(:)
14 allocate (t2 :: a)
15 allocate (t2 :: a2(5))
16 call move_alloc (from=a, to=b)
17 call move_alloc (from=a2, to=b2)
18 !print *, same_type_as (a,c), same_type_as (a,b)
19 !print *, same_type_as (a2,c2), same_type_as (a2,b2)
20 if (.not. same_type_as (a,c) .or. same_type_as (a,b)) STOP 1
21 if (.not. same_type_as (a2,c2) .or. same_type_as (a2,b2)) STOP 2
22 end