When a final subroutine is called

For Intel Fortran and gfortran, two cases where a FINAL subroutine of a derived type are called are when a local derived type goes out of scope in a procedure or when a local variable that is not allocatable or a pointer goes out of scope in a block (code below). I thought that the final subroutine would also be called when exiting blocks b2, b3, or b4. The Fortran standard in section “7.5.6.3 When finalization occurs” says

When a pointer is deallocated its target is finalized. When an allocatable entity is deallocated, it is finalized unless it is the variable in an intrinsic assignment statement or a subobject thereof. If an error condition occurs during deallocation, it is processor dependent whether finalization occurs.

module m
!
type :: vec
   real, pointer :: x(:) => null()
   contains
      final :: destructor
end type vec
!
contains
!
subroutine destructor(v)
type(vec) :: v
print*,"entering destructor, associated(v%x) =",associated(v%x)
if (associated(v%x)) deallocate (v%x)
print*,"leaving destructor, associated(v%x) =",associated(v%x)
end subroutine destructor
!
subroutine sub_alloc()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
print*,"in sub_alloc, v%x =",v%x
end subroutine sub_alloc
!
subroutine sub_automatic()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
print*,"in sub_automatic, v%x =",v%x
end subroutine sub_automatic
!
end module m
!
program main
use m, only: vec, sub_alloc, sub_automatic
implicit none
b1: block
   type(vec) :: v
   allocate (v%x(3))
   print*,"exiting b1"
end block b1
b2: block
   type(vec), allocatable :: v(:)
   allocate (v(3))
   print*,"exiting b2"
end block b2
b3: block
   type(vec), allocatable :: v(:)
   allocate (v(3))
   deallocate (v)
   print*,"exiting b3"
end block b3
b4: block
   type(vec), pointer :: v(:) => null()
   allocate (v(3))
   print*,"exiting b4"
end block b4
print*,"calling sub_alloc()"
call sub_alloc()
print*,"calling sub_automatic()"
call sub_automatic()
end program main

Output:

exiting b1
 entering destructor, associated(v%x) = T
 leaving destructor, associated(v%x) = F
 exiting b2
 exiting b3
 exiting b4
 calling sub_alloc()
 in sub_alloc, v%x =   10.00000       20.00000    
 entering destructor, associated(v%x) = T
 leaving destructor, associated(v%x) = F
 calling sub_automatic()
 in sub_automatic, v%x =   10.00000       20.00000    
 entering destructor, associated(v%x) = T
 leaving destructor, associated(v%x) = F
1 Like

One can think of FINAL as a generic interface to which one can either establish finalizer procedures for the ranks of objects to be finalized or an `ELEMENTAL’ procedure.

As shown in the original post, the generic interface only has finalizer for a rank-0 (scalar) object.

3 Likes

More flexibility that somehow made it into the standard with feature.

Consider abstraction toward vector calculus: conceivably, the finalization instructions toward objects of vector fields in one’s domain might differ with dimensionality. The existing semantics allows, at least in principle, the handling of such needs.

Practically though an ELEMENTAL finalizer might suffice in most situation.

Thanks @FortranFan. I made the destructor impure elemental. For the code

module m
!
type :: vec
   real, pointer :: x(:) => null()
   contains
      final :: destructor
end type vec
!
contains
!
impure elemental subroutine destructor(v)
type(vec), intent(in out) :: v
logical :: assoc_init
assoc_init = associated(v%x)
if (assoc_init) deallocate (v%x)
write (*,*) "leaving destructor, assoc_init, assoc_final =",assoc_init,associated(v%x)
end subroutine destructor
!
subroutine sub_alloc()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
print*,"in sub_alloc, v%x =",v%x
end subroutine sub_alloc
!
subroutine sub_automatic()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
print*,"in sub_automatic, v%x =",v%x
end subroutine sub_automatic
!
end module m
!
program main
use m, only: vec, sub_alloc, sub_automatic
implicit none
b1: block
   type(vec) :: v
   allocate (v%x(2))
   print*,"exiting b1 for scalar v"
end block b1
b2: block
   type(vec), allocatable :: v(:)
   allocate (v(2))
   print*,"exiting b2, size(v) =",size(v)
end block b2
b3: block
   type(vec), allocatable :: v(:)
   allocate (v(2))
   deallocate (v)
   print*,"exiting b3, allocated(v) =",allocated(v)
end block b3
b4: block
   type(vec), pointer :: v(:) => null()
   allocate (v(2))
   print*,"exiting b4, size(v)=",size(v)
end block b4
print*,"calling sub_alloc()"
call sub_alloc()
print*,"calling sub_automatic()"
call sub_automatic()
end program main

I get output with gfortran and Intel Fortran of

 exiting b1 for scalar v
 leaving destructor, assoc_init, assoc_final = T F
 exiting b2, size(v) =           2
 leaving destructor, assoc_init, assoc_final = F F
 leaving destructor, assoc_init, assoc_final = F F
 leaving destructor, assoc_init, assoc_final = F F
 leaving destructor, assoc_init, assoc_final = F F
 exiting b3, allocated(v) = F
 exiting b4, size(v)=           2
 calling sub_alloc()
 in sub_alloc, v%x =   10.0000000       20.0000000    
 leaving destructor, assoc_init, assoc_final = T F
 calling sub_automatic()
 in sub_automatic, v%x =   10.0000000       20.0000000    
 leaving destructor, assoc_init, assoc_final = T F

When exiting b2, I wonder why the destructor is called 4 times rather than twice, when size(v) = 2.

You’re dealing with the artifacts of processor-dependent actions leading to your puzzlement with the program behavior. Try the following:

Click to see
module m
!
type :: vec
   character(len=20) :: id = ""
   real, pointer :: x(:) => null()
   contains
      final :: destructor
end type vec
!
contains
!
impure elemental subroutine destructor(v)
type(vec), intent(in out) :: v
logical :: assoc_init
assoc_init = associated(v%x)
if (assoc_init) deallocate (v%x)
write (*,*) "leaving destructor, id, assoc_init, assoc_final = ",trim(v%id), assoc_init,associated(v%x)
end subroutine destructor
!
subroutine sub_alloc()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
v%id = "sub_alloc"
print*,"in sub_alloc, v%x =",v%x
end subroutine sub_alloc
!
subroutine sub_automatic()
type(vec) :: v
allocate (v%x(2))
v%x = [10.0,20.0]
v%id = "sub_automatic"
print*,"in sub_automatic, v%x =",v%x
end subroutine sub_automatic
!
end module m
!
program main
use m, only: vec, sub_alloc, sub_automatic
implicit none
b1: block
   type(vec) :: v
   v%id = "b1"
   allocate (v%x(2))
   print*,"exiting b1 for scalar v"
end block b1
b2: block
   type(vec), allocatable :: v(:)
   allocate (v(2))
   v(1)%id = "b2_1" ; v(2)%id = "b2_2"
   print*,"exiting b2, size(v) =",size(v)
end block b2
print *
b3: block
   type(vec), allocatable :: v(:)
   allocate (v(2))
   v(1)%id = "b3_1" ; v(2)%id = "b3_2"
   deallocate (v)
   print*,"exiting b3, allocated(v) =",allocated(v)
end block b3
b4: block
   type(vec), pointer :: v(:) => null()
   allocate (v(2))
   v(1)%id = "b4_1" ; v(2)%id = "b4_2"
   print*,"exiting b4, size(v)=",size(v)
end block b4
print*,"calling sub_alloc()"
call sub_alloc()
print*,"calling sub_automatic()"
call sub_automatic()
end program main

Attention also to anyone interested in finalization

  • Employ some suitable identifier scheme for the objects toward your book-keeping; a simple id component is used in the code above,

and/or BLOCK constructs in simple unit tests on Windows:

  • Do the equivalent of a system flush/clear message queue in between BLOCK constructs to keep the instructions in order if that is of interest; shown here with a simple PRINT statement.
2 Likes

@FortranFan Thank you. I was struggling destructors and found your example code. I doubt I would have ever thought about impure elemental .

1 Like

:+1:

Thiis makes sense once you know, but it’s definitely not intuitive…

Yes. It was blinding obvious in hindsight. I understand and use impure elemental.

1 Like