Finalization ifort vs gfortran

I am so desperate – it seems I don’t understand type finalization at all. It seems that gfortran (8.5.0) does too little (although that could be argued) while ifort (19.0.8) does too much. Since ifort is more likely to be conforming to the Fortran standard, I wonder what I am doing wrong or how I could achieve the behavior I’d like to achieve (I’ll explain that below).

First off, the example:

MODULE test
   TYPE T_TYPE1
      INTEGER :: a = 1111
   CONTAINS
      FINAL :: DESTROY_TYPE1
   END TYPE T_TYPE1

   INTERFACE t_type1
      MODULE PROCEDURE NEW_TYPE1
   END INTERFACE t_type1

CONTAINS

   FUNCTION NEW_TYPE1(a) RESULT(self)
      IMPLICIT NONE
      INTEGER :: a
      TYPE(T_TYPE1) :: self
      self%a = a
      WRITE(*,'(A,I0)') "Constructing type1: ", self%a
   END FUNCTION NEW_TYPE1

   SUBROUTINE DESTROY_TYPE1(self)
      TYPE(t_type1) :: self
      WRITE(*,'(A,I0)') "Finalizing type1: ", self%a
   END SUBROUTINE DESTROY_TYPE1


END MODULE test

PROGRAM testprog
  USE test
  INTEGER :: i
  TYPE(t_type1), ALLOCATABLE :: type1

  ALLOCATE(type1)
  WRITE(*,'(A,I0)') "Content (plain allocation): ", type1%a
  type1 = T_TYPE1(2)
  WRITE(*,'(A,I0)') "Content (explicit construction): ", type1%a
  DEALLOCATE(type1)

END PROGRAM testprog

The output of gfortran:

$ gfortran finalization.f90 -o finalization && ./finalization
Content (plain allocation): 1111
Constructing type1: 2
Content (explicit construction): 2
Finalizing type1: 2

The output of ifort:

$ ifort finalization.f90 -o finalization_i && ./finalization_i
Content (plain allocation): 1111
Constructing type1: 2
Finalizing type1: 1111
Finalizing type1: 2
Content (explicit construction): 2
Finalizing type1: 2

The second ifort finalization statement seems to do finalization of an object on the stack, or some kind of temporary object that is created upon explicit construction (it already has the a = 2 value). This is extremely unintuitve and leads to horrible behavior in my production code (stuff in a library is being unset that I actually want to use after assigning the constructed object to the LHS variable). So I’d like to get rid of that “extra” finalization.

I could deal with gfortran’s non-finalization of the plainly allocated type1 variable manually but I don’t know how to suppress the extra finalization that ifort does.

While searching for answers I saw it mentioned that Fortran 2003’s finalization is broken but I did not understand how to fix it (Finalisation in FORTRAN 2003 - Stack Overflow).

I just know that GFortran developers worked on finalization in 2023. See for example 80524 – [F03] Problematic behaviour with a finalization subroutine in gfortran

8.5.0 seems very old for that…

Yeah, the topic of finalization is pretty nuanced and there are some unexpected things.

Not necessarily, but in this case it would seem so. BTW, what version of gfortran are you using? Edit: just saw it. Yeah, 8.5 is quite old. I believe it has recently had fixes for type finalization.

Based on the rules in the standard, yes, I would expect to see the final subroutine called 3 times in your example.

In “7.5.6.3 When finalization occurs” of the standard

When an intrinsic assignment statement is executed (10.2.1.3), if the variable is not an unallocated allocatable variable, it is finalized after evaluation of expr and before the definition of the variable.

If an executable construct references a nonpointer function, the result is finalized after execution of the innermost executable construct containing the reference.

When an allocatable entity is deallocated, it is finalized unless it is the variable in an intrinsic assignment statement.

The “temporary” must exist for things like type1 = T_TYPE1(type1%a) or type1 = some_other_func(T_TYPE1(2)).

I find that type finalization often doesn’t end up being the right solution when I initially thought it might.

If found that gfortran 12.2.1 behaves the same as 8.5.0 regarding finalization.

I believe the type finalization stuff was maybe back-ported to 13.2.1, but is in 14+.

1 Like

GCC 14.0.1 is in the Fedora 40 Beta.

1 Like

With your test case, gfortran 14.0.1 output matches the ifort output.

1 Like

OK, thanks for the information and all responses. Unfortunately, I’m limited to ancient RedHat (RHEL8) which has offers gfortran 12 as the highest version in the default repos.

I’m very disappointed by OOP in Fortran now and I finally understand why people advise against using it )o:

I’ll try to rewrite my code now in a way that I don’t have to scrap all the OOP features I’ve already implemented such that it behaves the same in gfortran and ifort without side effects (obviously crashes and memory leaks). For any future code I’ll be extra careful to anticipate the issue finalization might bring about during object construction.

Here are my two cents about this. From what I understand about finalization, ifort behaves as expected and you see the first finalization because you used a constructor pattern. Fortran does not have a real constructor kind of thing and the interface is only a trick to mimic what other OOP languages do.
Since your constructor is a function, one object has to be created and upon assignment, i.e. type1 = T_TYPE1(2) the rhs gets finalized after all values of your object have been assigned to the lhs.
It would be different of course if you used some kind of initialization rather

  TYPE T_TYPE1
      INTEGER :: a = 1111
   CONTAINS
     PROCEDURE, PASS(self), PUBLIC :: INITIALIZE
      FINAL :: DESTROY_TYPE1
   END TYPE T_TYPE1
...
   SUBROUTINE INITIALIZE(self, a)
     TYPE(T_TYPE1), INTENT(INOUT) :: self
     INTEGER, INTENT(IN) :: a
     self%a = a
   END SUBROUTINE

By doing so, you would not create an intermediate object and therefore, there would be no final call.

Now, I also observed that sometimes gfortran behaves oddly with auto allocation of derived types upon assignment. Before rewriting your code you may want to try to change the line

type1 = T_TYPE1(2)

By an explicit allocation

allocate(type1, source = T_TYPE1(2))

Good luck

1 Like

The point is not OO but memory management. You can still write in a OO style using allocatable variables without any explicit memory management.

Yeah, I’ve now done as much as I can using allocatables.

But the problem really was that I allocated memory in a constructor (via some c library call) which I wanted to release in the FINAL routine. In that case, the FINAL routine executed when cleaning up the temporary RHS object before assignment already had the reference for the allocated object. It cleared that memory so it was undefined when I actually wanted to access it from the newly constructed object assigned to the LHS.

The solution, as it seems, is not to allocate that memory in the constructor but elsewhere after construction, and IF-guard its deallocation in the final routine. Not so elegant but at least it works.

I’ve encountered this problem before, where the finalizer works “earlier” than you expect it too.

type :: holds_pointer
   type(c_ptr) :: handle = c_null_ptr   ! points to heap memory
contains
   final :: shutdown       ! releases the handle
   procedure :: use_handle
end type

type(holds_pointer) :: instance

instance = create_instance()
call instance%use_handle()  ! KA-BOOM! (Invalid handle)

The problem is really not the finalizer, but the fact that object creation, destruction, and copying are tightly linked operations. In C++ they call this the rule of three or “the big three”. Quoting Wikipedia, the rule claims that if a class defines any of the following then it should probably explicitly define all three:

  • destructor
  • copy constructor
  • copy assignment operator

Fortran doesn’t have such a thing as a copy constructor. You could fix the problem by overloading the assignment operator, but this has it’s own subtle problems (i.e. does the assignment perform a deep copy or a shallow copy of the pointer?).

There are (at least) two ways to fix this:

You should have a look then at what is done in symengine.f90 then. It’s pretty much the same as what you describe. The memory is allocated from a c library in the constructor

but then you need a finalizer (basic_free) AND to overload the assignment (basic_assign).
You also may not need allocatables.

1 Like

That’s a good example of how final and assignment(=) go hand-in-hand.

You might also be interested in this library:

I’ve now converted all my “constructors” to some kind of “initializer method”, like this:

TYPE T_TYPE1
      INTEGER :: a = 1111
   CONTAINS
     PROCEDURE :: new => NEW_TYPE1
     FINAL :: DESTROY_TYPE1
END TYPE T_TYPE1
...
   SUBROUTINE NEW_TYPE1(self, a)
     CLASS(T_TYPE1) :: self
     INTEGER, INTENT(IN) :: a
     self%a = a
   END SUBROUTINE

and use it like this:

ALLOCATE(type1)
CALL type1%new(2)

This might not be the prettiest method but I’m quite satisfied with it nevertheless as it not too hard to comprehend when reading the code (the new-call) and seems safer than the “constructor approach”.

I would suggest a couple tweaks.

TYPE T_TYPE1
      PRIVATE; LOGICAL :: UNUSED ! prevent intrinsic structure constructor
      INTEGER :: a = 1111
   CONTAINS
     PROCEDURE :: new => NEW_TYPE1
     FINAL :: DESTROY_TYPE1
END TYPE T_TYPE1
...
   SUBROUTINE NEW_TYPE1(self, a)
     CLASS(T_TYPE1), INTENT(INOUT) :: self ! prevent unmodifiable argument
     INTEGER, INTENT(IN) :: a
     self%a = a
   END SUBROUTINE

to prevent code like the following from exploding at runtime

associate(t => t_type1(42))
  call t%new_type1(1729)
end associate