Retro68/gcc/gcc/testsuite/gfortran.dg/defined_assignment_9.f90
2018-12-28 16:30:48 +01:00

46 lines
884 B
Fortran

! { dg-do run }
!
! PR fortran/57697
!
! Further test of typebound defined assignment
!
module m0
implicit none
type component
integer :: i = 42
contains
procedure :: assign0
generic :: assignment(=) => assign0
end type
type parent
type(component) :: foo
end type
contains
elemental subroutine assign0(lhs,rhs)
class(component), intent(INout) :: lhs
class(component), intent(in) :: rhs
lhs%i = 20
end subroutine
end module
program main
use m0
implicit none
block
type(parent), allocatable :: left
type(parent) :: right
! print *, right%foo
left = right
! print *, left%foo
if (left%foo%i /= 20) STOP 1
end block
block
type(parent), allocatable :: left(:)
type(parent) :: right(5)
! print *, right%foo
left = right
! print *, left%foo
if (any (left%foo%i /= 20)) STOP 2
end block
end