Let’s take an abstract base type which defines an interface and an extending type, which implements this interface and uses internally pointers. In order to handle the assignment correctly, it overrides the assignment operator. Now, in which of the cases below is the processor supposed to invoke the defined assignment:
-
class(base)
[allocated to atype(ext)
instance] =type(ext)
-
class(base)
[unallocated] =type(ext)
-
class(ext)
[allocated to atype(ext)
instance] =type(ext)
-
class(ext)
[unallocated] =type(ext)
Demonstration code
module test
implicit none
type, abstract :: base_t
end type base_t
type, extends(base_t) :: ext_t
integer :: val = 0
contains
procedure :: ext_assign
generic :: assignment(=) => ext_assign
end type
contains
subroutine ext_assign(this, other)
class(ext_t), intent(out) :: this
type(ext_t), intent(in) :: other
print *, "ASSIGNMENT ext_assign invoked"
this%val = other%val
end subroutine ext_assign
end module test
program testprog
use test
implicit none
print "(/,a)", "*** ASSIGNMENT TO ALLOCATED BASE (WITH DYNAMIC TYPE EXT)"
block
class(base_t), allocatable :: base
class(ext_t), allocatable :: ext
allocate(ext)
call move_alloc(ext, base)
print *, "BASE allocated now with dynamic type EXT"
base = ext_t(1)
print *, "ASSIGNMENT DONE"
end block
print *, "BLOCK DONE"
print "(/,a)", "*** ASSIGNMENT TO UNALLOCATED BASE"
block
class(base_t), allocatable :: base
base = ext_t(2)
print *, "ASSIGNMENT DONE"
end block
print *, "BLOCK DONE"
print "(/,a)", "*** ASSIGNMENT TO ALLOCATED EXT"
block
class(ext_t), allocatable :: ext
allocate(ext)
print *, "BASE allocated now with dynamic type EXT"
ext = ext_t(3)
print *, "ASSIGNMENT DONE"
end block
print *, "BLOCK DONE"
print "(/,a)", "*** ASSIGNMENT TO UNALLOCATED EXT"
block
class(ext_t), allocatable :: ext
ext = ext_t(4)
print *, "EXT allocated now"
ext = ext_t(5)
print *, "ASSIGNMENT DONE"
end block
print *, "BLOCK DONE"
end program testprog
As my tests with the self-containing program above suggest, cases 1 and 2 use intrinsic assignment, while cases 3 and 4 use the user defined one. (Case 4 leads to a segfault as user defined assignment does not allocate the LHS.)
- Is that the expected behavior as defined by the standard?
If yes, it raises several questions to me:
-
Does this mean, that the consumer of a derived type must be aware, whether the type overrides assignment or not?
Since in the latter case, it can not rely on the automatic allocation of the LHS, leading to a segfault, as in my
example. -
In case 2, if the derived type on the RHS is copied to the LHS (and then finalized as suggested by the discussion in Finalization/Copy in intrinsic polymorphic assignment) this would lead to catastrophic results: The user defined assignment would be not invoked (so pointed content not duplicated), but due to the finalization of the RHS probably destroyed, so the LHS had broken pointers. (It would also make reference counting techniques impossible…)
So it seems to me, that in a robust programming model, assignment between derived types and classes must be best avoided, also at the consumer side, otherwise lacking knowledge on the implementation details of the type/class can lead to unwanted side effects (segfaults). Is that conclusion correct?
Any comments sheding more light on this are welcome. Please also note, my purpose is not to criticize the language but to understand which techniques for implementing robust containers (where the consumer has not to care about the internal implementational details of the container) are possible with the current features (and current compilers). And maybe also to think about possible language extensions for future standards, which could ease this task.