Intrinsic assigment of derived types containing components with user defined assignment

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.

I believe that Section 7.2.1.4 of the Fortran standard is what you’re looking for:

I interpret condition (3) (“the types of d1 and d2 are compatible with the dynamic types of x1 and x2, respectively”) so that you and the Intel compiler got this right.

I’ve been doing some work involving defined assignments and finalization recently and have encountered multiple compiler bugs along the way. I’m by no means any expert in the field, but my impression is that the Fortran standard has some very odd decision which makes working with defined assignments and finalization very difficult. I really hope that this could be improved on in the future. Having control over memory, including assignment and finalization is a crucial part of writing robust libraries and that is ultimately the foundation of this community!

For whatever it’s worth, the wording in the standard informs me the behavior of the program processed using the Intel compiler conforms. I suggest you submit support requests with the vendors of the other two compilers.

As pointed out in the other comment, section 10.2.1.3 Interpretation of intrinsic assignments provides the basis for the behavior to be as you expect, especially paragraph 13 on lines 4 thru’ 8 on page 163, “An intrinsic assignment where the variable is of derived type is performed as if each component of the variable were assigned from the corresponding component of expr using … defined assignment for each nonpointer nonallocatable component of a type that has a type-bound defined assignment consistent with the component, intrinsic assignment for each other nonpointer nonallocatable component …” (emphasis mine).

P.S.> I personally think this is a situation where Intel is first off-the-block when it comes to bug fixes following the Fortran 2008 feature introduction of allocation-upon-assignment of polymorphic objects; the others are getting there. Almost all the implementations appear to have started off their work with the semantics in Fortran 2003 that did not allow this and the relevant sections had to be revised later with varying success rate, as can be here unfortunately.

@plevold @FortranFan Thanks a lot for your insights. I’ll make bug reports for the affected compilers.