Finalization of class arrays; interpretation of standards

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

4 Likes

Hi @abensonca thanks for the post and welcome to Discourse! I can see you also posted the same question here:

and already got a few responses.

Hi @certik - thanks. Yes - I think the answers over on GitHub make it clear that ifort’s behavior here is incorrect.

I’ll probably have a few more questions related to finalization of class arrays over the next few days.

1 Like

Anytime! Thank you again for working on GFortran. We all appreciate it as GFortran is the most production ready (in my opinion) open source Fortran compiler that we have.

The NAG Fortran compiler (7.0) agrees with gfortran (8.4.1 and 11.2.0) and disagrees with ifort (2021.2.0).

1 Like

For whatever it’s worth and I’m open to being proved wrong on this: I think Intel Fortran’s finalization process toward the code in the original post vis-a-vis the standard is entirely acceptable.

Note the standard is (purposefully I think) not prescriptive when it comes to the finalization process, there is a desired end state of a finalized entity in the standard even as it is not clearly spelled out. Nonetheless the standard effectively permits the processors multiple pathways to arrive at that end state. Comparison of those pathways, which is what the original post attempts, is not particularly meaningful in this context, at least as the standard is currently written,

Section 7.5.6.2 The finalization process in 18-007r1 document toward the 2018 standard by and large gives a lot of leeway to the processor and there are no numbered rules or constraints in this section enforcing the program or processor behavior.

Taking into the consideration the first paragraph in section 7.5.6.2 and the numbered bullets therein in conjunction with section 7.5.7 on type extension, a fair argument can be made the finalization process in the following code is analogous to the one in the original post:

module m
   type :: a_t
   contains
      final :: f_a_r0
   end type
   type :: b_t
      type(a_t) :: a
   contains
      final :: f_b_r0, f_b_r1
   end type 
contains
   subroutine f_a_r0( a )
      type(a_t), intent(inout) :: a
      print *, "finalizer rank-0 a_t"
   end subroutine 
   subroutine f_b_r0( b )
      type(b_t), intent(inout) :: b
      print *, "finalizer rank-0 b_t"
   end subroutine 
   subroutine f_b_r1( b )
      type(b_t), intent(inout) :: b(:)
      print *, "finalizer rank-1 b_t"
   end subroutine 
end module
   use m
   block
      type(b_t) :: foo(3)
   end block
end 

And for this, a standard-conforming processor can be expected to yield the following program behavior:

C:\Temp>ifort /standard-semantics f.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.

-out:f.exe
-subsystem:console
f.obj

C:\Temp>f.exe
finalizer rank-1 b_t
finalizer rank-0 a_t
finalizer rank-0 a_t
finalizer rank-0 a_t

as does Intel Fortran and NAG Fortran (though not gfortran**).

Ostensibly the 2 processors in this case simply follow the steps in section 7.5.6.2 and there is no argument to be made about any processor nonconformance with the simple code here. The key sentences in the standard are “If the entity being finalized is an array, each finalizable component of each element of that entity is finalized separately” followed by “If the entity is of extended type and the parent type is finalizable, the parent component is finalized”

And what Intel Fortran does with the code in the original post is consistent with this and I think it is conformant with the standard.

** gfortran has gaps when it comes to finalization of nonallocatable but finalizable objects, the code here is an example of this.
@abensonca, you may be interested in including this case in your work.