Yes, but I somehow missed the part highlighting the difference between a type()
variable and a class()
variable.
Intel warns about this, but since the type in my example does not have any data an initialized and an uninitialized variable is exactly the same.
It’s not a desire to use defined assignment itself, but rather a absolute need for it. When using pointer
-s or type(c_ptr)
in a derived type it is crucial to implement both assignment and finalization to avoid memory leaks, double frees or invalid memory access. In fact, the standard even notes this:
NOTE 4.49
If finalization is used for storage management, it often needs to be combined with defined assignment.
In current versions of ifort and gfortran however, declaring the variable as class(base_t), allocatable
instead of type(my_t)
will introduce memory issues if data has been allocated behind a pointer
or a type(c_ptr)
. If one does
class(base_t), allocatable :: x, y
x = my_t()
y = x
the variables x
and y
will now share the data behind the pointers!
Complete example
module my_mod
implicit none
type, abstract :: base_t
end type
type, extends(base_t) :: my_t
integer, pointer :: val => null()
contains
procedure, private :: assign
generic :: assignment(=) => assign
final :: finalize
end type
interface my_t
module procedure :: init
end interface
contains
type(my_t) function init() result(this)
write(*,*) 'init'
allocate(this%val)
this%val = 42
end function
subroutine assign(lhs, rhs)
class(my_t), intent(out) :: lhs
type(my_t), intent(in) :: rhs
write(*,*) 'assign'
allocate(lhs%val)
lhs%val = rhs%val
end subroutine
subroutine finalize(this)
type(my_t), intent(inout) :: this
write(*,*) 'finalize'
if (associated(this%val)) then
deallocate(this%val)
end if
end subroutine
end module
program main
use my_mod, only: base_t, my_t
implicit none
write(*,*) 'Concrete type example'
block
type(my_t) :: x, y
x = my_t()
y = x
write(*,*) 'loc x%val: ', loc(x%val)
write(*,*) 'loc y%val: ', loc(y%val)
end block
write(*,*) 'Concrete type example done'
write(*,*)
write(*,*) 'Abstract base class example'
block
class(base_t), allocatable :: x, y
x = my_t()
y = x
select type (x)
type is (my_t)
write(*,*) 'loc x%val: ', loc(x%val)
end select
select type (y)
type is (my_t)
write(*,*) 'loc y%val: ', loc(y%val)
end select
end block
write(*,*) 'Abstract base class example done'
write(*,*)
end program
Output:
Concrete type example
init
finalize
assign
finalize
finalize
assign
loc x%val: 32937120
loc y%val: 32937184
finalize
finalize
Concrete type example done
Abstract base class example
init
finalize
loc x%val: 32937248
loc y%val: 32937248
finalize
finalize
Abstract base class example done
free(): double free detected in tcache 2
Aborted
I’m still not sure exactly why this is standard conformant so I need to do some more reading…
This now works with a variable declared as class(b_t), allocatable
, but now the memory issues will occur for a variable declared as type(e_t)
. Also, one have to remember NOT to do use m, only: b_t
, but rather use m, only: b_t, assignment(=)
or else one will introduce memory issues again. Not very robust in my opinion. Intel let’s me combine our two suggestions into one, but gfortran complains about this:
Two defined assignments
module my_mod
implicit none
type, abstract :: base_t
end type
type, extends(base_t) :: my_t
contains
procedure, private :: assign
generic :: assignment(=) => assign
final :: finalize
end type
interface my_t
module procedure :: init
end interface
interface assignment(=)
module procedure assign_base
end interface
contains
type(my_t) function init() result(this)
write(*,*) 'init '!, loc(this%inner)
end function
subroutine assign_base(lhs, rhs)
class(base_t), allocatable, intent(out) :: lhs
type(my_t), intent(in) :: rhs
write(*,*) 'assign base', loc(lhs), ' -> ', loc(rhs)
allocate(lhs, mold=rhs)
end subroutine
subroutine assign(lhs, rhs)
class(my_t), intent(out) :: lhs
type(my_t), intent(in) :: rhs
write(*,*) 'assign', loc(lhs), ' -> ', loc(rhs)
end subroutine
subroutine finalize(this)
type(my_t), intent(inout) :: this
write(*,*) 'finalize ', loc(this)
end subroutine
end module
gfortran error:
112 | subroutine assign_base(lhs, rhs)
| 1
......
121 | subroutine assign(lhs, rhs)
| 2
Error: Ambiguous interfaces in intrinsic assignment operator for ‘assign_base’ at (1) and ‘assign’ at (2)
Using an inner type as @aradi suggested in the previous post works well on Intel. If the bug is fixed in gfortran et. al. this might be the preferred approach.