Dear all,
Can anybody tell me, what the standard complying result of the demonstration code below should be? I get different results, with different compilers (intel: 40, nag, gnu, nvidia: 41).
Update (2022-02-09): The bug had been fixed in the newest build of the NAG compiler (both, version 7.0 and 7.1).
assignment of a derived type with a component with user defined assignment
module testmod
implicit none
! Wrapping everything dirty (needing user defined assignment into a special type)
type :: dirty_t
integer :: val = -1
contains
procedure :: dirty_assign
generic :: assignment(=) => dirty_assign
end type dirty_t
! Extends abstract interface
type :: container_t
type(dirty_t) :: dirty
end type container_t
contains
subroutine dirty_assign(this, other)
class(dirty_t), intent(out) :: this
type(dirty_t), intent(in) :: other
this%val = other%val - 1
print "(a, i0, a, i0, a)", "dirty_assign (", other%val, " -> ", this%val, ")"
end subroutine dirty_assign
end module testmod
program testprog
use testmod
implicit none
type(container_t), allocatable :: stat1, stat2
class(container_t), allocatable :: dyn
allocate(stat1)
stat1%dirty%val = 42
stat2 = stat1
print "(a, i0)", "stat2 value: ", stat2%dirty%val
dyn = stat2
print "(a, i0)", "dyn value: ", dyn%dirty%val
end program testprog
Or to phrase the question more generally, if a derived type wraps (in the sense of containing as a component) an other derived type with user defined assignment, should the intrinsic assignment of the wrapper type trigger the user defined assignment for that component?
- It seems, that compilers agree, that the user defined assignment of the component should be triggered if you assign a type to a type:
type(container_t), allocatable :: stat1, stat2 allocate(stat1) stat1%dirty%val = 42 ! Next assignment invokes the defined assignment of stat1%dirty with all compilers stat2 = stat1
- It seems, that compilers absolutely disagree, when the LHS is a class with dynamic type:
type(container_t), allocatable :: stat2 class(container_t), allocatable :: dyn allocate(stat2) stat2%dirty%val = 42 ! Next assignment invokes defined assignment of stat2%dirty with intel, ! but not with nag or gnu dyn = stat2
It feels to me, that the second case should behave as the first one (triggering the user defined assignment of the component), but maybe somebody with deeper knowledge of the standard can shed some light on this.