I am trying to understand the consequences of the polymorphic intrinsic assignment, especially, whether it can be warranted, that it always behaves move_alloc
-like without creating (and finalizing) a temporary copy. I hope, somebody with deeper knowledge can comment on that.
The toy example below shows a container, which extends a basic type (which would normally contain the generic interface of that container type). The specific implementation stores its value in form of an allocated pointer and is created by making a polymorphic assignment, with a user defined structure constructor on its RHS. I find this solution very elegant, but I am wondering, whether I can rely on, that no temporary copy is made during this assignment (as its finalization would result in an invalid pointer).
module test
implicit none
type :: base_t
end type base_t
type, extends(base_t) :: ext_t
integer, pointer :: ptr => null()
contains
final :: ext_final
end type
interface ext_t
module procedure ext_construct
end interface
contains
function ext_construct(val) result(this)
integer, intent(in) :: val
type(ext_t) :: this
allocate(this%ptr)
this%ptr = val
end function ext_construct
subroutine ext_final(this)
type(ext_t), intent(inout) :: this
print *, "FINALIZER ext_final invoked"
if (associated(this%ptr)) deallocate(this%ptr)
end subroutine ext_final
end module test
program testprog
use test
implicit none
class(base_t), allocatable :: base
! Is it warranted, that next line never makes a temporary copy
! and never triggers the finalizer of an ext_t instance?
base = ext_t(42)
print *, "ASSIGNMENT DONE"
deallocate(base)
end program testprog
I know, that I could “enforce” the move_alloc
like behavior by doing it explicitely:
type(ext_t), allocatable :: ext
class(base_t), allocatable :: base
allocate(ext)
call ext_init(ext, 42) !<-- Needs an extra subroutine ext_init, which does the initialization
call move_alloc(ext, base)
but I find it less elegant and less expressive than the polymorphic assignment.