I’m working (with much help from Paul Thomas) on adding finalization on intrinsic assignment to gfortran. There are a few instances where I’m unclear on precisely what is required by the standard, so would be very grateful for any insight any one here can offer.
This example considers finalization of a class array:
module testmode
implicit none
character(4) :: scope = "MAIN"
logical, parameter :: instrument = .false.
type :: simple
character(4) :: scope
integer :: ind
contains
final :: destructor1, destructor2
end type simple
type, extends(simple) :: complicated
real :: rind
contains
final :: destructor3, destructor4
end type complicated
integer :: check_scalar
integer :: check_array(4)
real :: check_real
real :: check_rarray(4)
integer :: final_count = 0
contains
subroutine destructor1(self)
type(simple), intent(inout) :: self
print *, "destructor1(", self%scope, ") ", self%ind
end subroutine destructor1
subroutine destructor2(self)
type(simple), intent(inout) :: self(:)
print *, "destructor2(", self(1)%scope, ") ", self%ind
end subroutine destructor2
subroutine destructor3(self)
type(complicated), intent(inout) :: self
print *, "destructor3(", self%scope, ") ", self%rind
end subroutine destructor3
subroutine destructor4(self)
type(complicated), intent(inout) :: self(:)
if (size(self, 1) .gt. 0) then
print *, "destructor4(", self(1)%scope, ") ", size(self%rind), self%rind
else
print *, "destructor4"
end if
end subroutine destructor4
function constructor1(ind) result(res)
type(simple), allocatable :: res
integer, intent(in) :: ind
scope = "CTR1"
allocate (res, source = simple ("SOUR", ind))
res%scope = scope
end function constructor1
function constructor2(ind, rind) result(res)
class(simple), allocatable :: res(:)
integer, intent(in) :: ind(:)
real, intent(in), optional :: rind(:)
type(complicated), allocatable :: src(:)
integer :: sz
integer :: i
scope = "CTR2"
if (present (rind)) then
sz = min (size (ind, 1), size (rind, 1))
src = [(complicated ("SOUR", ind(i), rind(i)), i = 1, sz)]
allocate (res, source = src)
src%scope = "SRC "
res%scope=scope
else
sz = size (ind, 1)
allocate (res, source = [(simple (scope, ind(i)), i = 1, sz)])
end if
end function constructor2
end module testmode
program test_final
use testmode
implicit none
class(simple), allocatable :: MyClassArray(:)
! *****************
! Class assignments
! *****************
allocate (MyClassArray, source = [complicated(scope, 1, 2.0),complicated(scope, 3, 4.0)])
print *, "[3] ...until here. Both call the rank-1 finalizer for the extended &
type but ifort calls the rank-0 finalizer for the parent type, while &
gfortran uses the rank-1 finalizer."
deallocate (MyClassArray)
end program test_final
With gfortran (including the patches for finalization on intrinsic assignment that I’m working on), this results in:
[3] ...until here. Both call the rank-1 finalizer for the extended type but ifort calls the rank-0 finalizer for the parent type, while gfortran uses the rank-1 finalizer.
destructor4(MAIN) 2 2.00000000 4.00000000
destructor2(MAIN) 1 3
which shows that, when deallocating ‘MyClassArray
’, the rank-1 finalizer for the extended type ‘complicated
’ is called, and then the rank-1 finalizer for the parent type ‘simple
’ is called.
But, under ifort I get:
[3] ...until here. Both call the rank-1 finalizer for the extended type but ifo
rt calls the rank-0 finalizer for the parent type, while gfortran uses the rank
-1 finalizer.
destructor4(MAIN) 2 2.000000 4.000000
destructor1(MAIN) 1
destructor1(MAIN) 3
showing that the rank-1 finalizer is called for the extended type, but then the scalar finalizer of the parent type is called twice, once for each element in the array.
ifort’s behavior seems incorrect here (based on my reading of the F2018 standards), but I’d be interested to hear anyone’s opinion on this.
Thanks,
Andrew