Should we avoid assignment of derived types in robust programs?

@ivanpribec It seems, that indirection/wrapping is a robust solution for hiding implementation details (thanks for bringing up the idea!) when user defined assignment is involved. (And probably the only one, if the ambiguity demonstrated in Should we avoid assignment of derived types in robust programs? - #32 by aradi can not be resolved within the rules of the standard).

The program below demonstrates it: A container type (type(contaminated)) outsources its components requiring user defined assignments into a special type (type(dirty)). If only type(contaminated) is exposed to the consumer, it behaves like an intrinsic type in all assignments:

  • assigning to a static instance works
  • assigning to an allocatable instance works as well
  • as a bonus, even assignment to arrays of arbitrary rank works

And all this only requires one to override the assignment in type(dirty) for the scalar, static case!!!

It seems, that as so often in Fortran, wrapping is the solution. :smile: (As long, as the user does not make a sourced allocation, but that should be probably really avoided for any non-intrinsic type anyway… :wink: )

So the rule for derived types in robust programming would then read

Never expose a derived type with user defined assignment to the users of your library. If a derived type needs user defined assignment, make it a component of a derived type with intrinsic assignment and expose latter.

module testmod
  implicit none

  private
  public :: contaminated

  type :: dirty
    integer :: value = 0
  contains
    procedure :: dirty_assign
    generic :: assignment(=) => dirty_assign
  end type dirty

  type :: contaminated
    type(dirty) :: contamination
  end type contaminated

contains

  subroutine dirty_assign(this, other)
    class(dirty), intent(out) :: this
    type(dirty), intent(in) :: other

    this%value = other%value + 1
    print "(a,i0,a,i0,a)", "dirty assign (", other%value, "->", this%value, ")"

  end subroutine dirty_assign

end module testmod


program testprog
  use testmod
  implicit none

  type(contaminated) :: static1, static2
  type(contaminated), allocatable :: alloc
  type(contaminated) :: static_array1(2), static_array2(2)
  class(contaminated), allocatable :: dynamic_contaminated

  print "(a)", "static2 = static1"
  static2 = static1
  print "(a)", "static_array1 = static_array2"
  static_array2(:) = static_array1
  print "(a)", "alloc1 = static1"
  alloc = static1
  print "(a)", "dynamic_contaminated = static1"
  dynamic_contaminated = static1

end program testprog

Note: due to compiler bugs (see Intrinsic assigment of derived types containing components with user defined assignment), the code above currently only works with the Intel compiler, but not with GNU, NAG or NVidia. (bugs reported)