Final procedure for polymorphic base type

I’m trying to improve fortran-yaml-c. A key issue right now is that memory is not automatically deallocated, which can lead to memory leaks if you are not careful. However, I can not figure out how to implement a a final procedure which will work in my case.

Below I give a more simple example (compared to yaml_types.f90 in fortran-yaml-c) which sort-of illustrates the problem. I have polymorphic derived types tied together with pointers. This allows containment of an abstract number of nested lists and values.

I want to attach a final procedure to type Node. When the “root” node goes out of scope, then this procedure would delete the big web of data connected to it. This isn’t possible, because according to gfortran, I can not have a final procedure for a polymorphic type.

Any advice is appreciated!

module test
  implicit none

  type :: Node
  contains
  procedure :: finalize => node_finalize
  end type

  type :: list_item
    type(list_item), pointer :: next => null()
    type(Node), pointer :: n => null()
  end type

  type, extends(Node) :: List
    type(list_item), pointer :: first => null()
  contains
    procedure :: finalize => list_finalize
  end type
  
  type, extends(Node) :: Scalar
    character(:), allocatable :: s
  end type

contains

  recursive subroutine node_finalize(self)
    class(Node), target, intent(inout) :: self
  end subroutine

  recursive subroutine list_finalize(self)
    class(List), target, intent(inout) :: self

    type(list_item), pointer :: item, next

    item => self%first
    do while (associated(item))
      next => item%next
      call item%n%finalize()
      deallocate(item%n)
      deallocate(item)
      item => next
    end do
    nullify(self%first)
  end subroutine

end module
2 Likes

I compiled your snippet without any errors (gcc version 12.1.0) are you targeting a specific compiler? Using the flag -fsanitize=address may be useful for you to identify memory leaks.

If your type(List) encapsulates the current existing nodes, by freeing the current nodes in the list, and in each deletion operation, you will not need to provide a final to the Node itself, unless the Node will be used by a client code directly (which I think is not a good idea).

1 Like

@nicholaswogan ,

You will note in Fortran specifically and with the object-oriented paradigm generally, there is no concept of a final procedure for a polymorphic base type.

Basically, you will notice in the standard a finalizer goes with a concrete “class” aka a non-abstract derived type extension.

But now if a derived type extends a type which has a finalizer, the extended type does not inherit any of the final procedures of the parent type. Rather, the situation is for the extended type to have its own final procedures also i.e., if there is such a need. This may be the case for example when the extended type too has its own derived type components that have the POINTER attribute that are allocated directly with the ALLOCATE statement, meaning to anonymous objects of the TARGET attribute. Or when the extended type taps into other resources (open files or databases, etc.) which then need to be released when the object is destroyed. Otherwise, the extended type can do without a specific final procedure - here note though the extended type remains a finalizable type.

Then when an object of the extended type is finalized (since it is finalizable as mentioned above), the steps specified in the standard are taken. So if the extended type has a finalizer, it will be invoked. Then after the extended type is finalized, the standard stipulates for the parent type, which - note - is a component of the extended type, to be finalized and here, if the parent has a finalizer, it gets invoked.

So you can use the above semantics to design the parent type corresponding to your Node “class”. Based on what you show though in the original post, no final procedure appears to be warranted for it. Regardless, you decide if it needs one. And then the authors who extend this Node “class”, who may be yourself!, can decide if the type extensions need final procedures or whether a well-designed Node parent type can do the needful with its final method.

1 Like

@14ngp Sorry I didn’t explain well. I think my simple example doesn’t do the problem too much justice.

@FortranFan thanks for your response. I think I sort understand.

I’ve settled on the following solution for fortran-yaml-c: Wrap the “root” node of the yaml data in a derived type that itself has a final procedure:

  type :: YamlFile
    class(type_node), pointer :: root => null()
  contains 
    procedure :: parse => YamlFile_parse
    procedure :: dump => YamlFile_dump
    final :: YamlFile_final
  end type
  ! ...
  subroutine YamlFile_final(self)
    type(YamlFile), intent(inout) :: self
    if (associated(self%root)) then
      call self%root%finalize()
      deallocate(self%root)
      nullify(self%root)
    endif
  end subroutine
1 Like

Thanks. I was recently failing with something similar. This conversation is helpful.