blob: b62a023a9eabb60b502193d6cfc2981852b28c83 [file] [log] [blame]
! { dg-do run }
!
! Test move_alloc for polymorphic scalars
!
!
module myalloc
implicit none
type :: base_type
integer :: i =2
end type base_type
type, extends(base_type) :: extended_type
integer :: j = 77
end type extended_type
contains
subroutine myallocate (a)
class(base_type), allocatable, intent(inout) :: a
class(base_type), allocatable :: tmp
allocate (extended_type :: tmp)
select type(tmp)
type is(base_type)
call abort ()
type is(extended_type)
if (tmp%i /= 2 .or. tmp%j /= 77) call abort()
tmp%i = 5
tmp%j = 88
end select
select type(a)
type is(base_type)
if (a%i /= -44) call abort()
a%i = -99
class default
call abort ()
end select
call move_alloc (from=tmp, to=a)
select type(a)
type is(extended_type)
if (a%i /= 5) call abort()
if (a%j /= 88) call abort()
a%i = 123
a%j = 9498
class default
call abort ()
end select
if (allocated (tmp)) call abort()
end subroutine myallocate
end module myalloc
program main
use myalloc
implicit none
class(base_type), allocatable :: a
allocate (a)
select type(a)
type is(base_type)
if (a%i /= 2) call abort()
a%i = -44
class default
call abort ()
end select
call myallocate (a)
select type(a)
type is(extended_type)
if (a%i /= 123) call abort()
if (a%j /= 9498) call abort()
class default
call abort ()
end select
end program main