Help working around finalization issue

When you have derived type with pointer compoments and a finalizer, you likely need to overload assignment too, depending in which way you initialize the DT. This is related to the so-called “rule of three”: Rule of three (C++ programming) - Wikipedia

The reason I say likely, is because it depends how you create an instance of that DT which could be either using an assignment or a call to a subroutine (could be type-bound).

If you need to use defined assignment and your type has pointer components, try to follow the advice given here: Should we avoid assignment of derived types in robust programs? - #35 by FortranFan


Edit: here is an example of how this issue manifests

module ill_t

use, intrinsic :: iso_c_binding
implicit none
private

public :: t
public :: t_of_size
public :: t_print

type :: t
    real(c_float), pointer :: a(:) => null()
contains
    final :: t_destroy
end type

interface
    function c_malloc(size) bind(c,name="malloc")
        import c_size_t, c_ptr
        integer(c_size_t), value :: size
        type(c_ptr) :: c_malloc
    end function
    subroutine c_free(ptr) bind(c,name="free")
        import c_ptr
        type(c_ptr), value :: ptr
    end subroutine
end interface

contains

    subroutine t_destroy(this)
        type(t), intent(inout) :: this
        if (associated(this%a)) then
            call c_free(c_loc(this%a))
            nullify(this%a)
        end if
    end subroutine

    function t_of_size(n) result(this)
        integer, intent(in) :: n
        type(t) :: this
        
        type(c_ptr) :: p
        integer :: i

        p = c_malloc(n*c_sizeof(1.0_c_float))
        if (c_associated(p)) then
            call c_f_pointer(p,this%a,[n])
        else
            return
        end if

        ! Initialize memory
        do i = 1, n
            this%a(i) = i
        end do

    end function

    subroutine t_print(tt)
        type(t), intent(in) :: tt
        if (associated(tt%a)) print *, tt%a 
    end subroutine

end module

program test

    use ill_t

    type(t) :: my_t

    my_t = t_of_size(5)  ! Seemingly okay 

       ! 1) left-hand side is finalized
       ! 2) right-hand side temporary created
       ! 3) intrinsic assignment (shallow copy pointer component)
       ! 4) right-hand side temporary is finalized
       ! 5) my_t has corrupt data member t%a (use-after-free)

    call t_print(my_t) ! expecting [ 1,2,3,4,5 ], instead garbage

end program

The reason this breaks is because the “lifetime management” of the object is inconsistent. We’ve specified the creation and destruction, but we haven’t specified the copy/assignment (rule of three). Removing the finalizer solves the problem, but then it’s up to the user to destroy the object (prevent a memory leak). The solution is to provide an assignment, but this has some subtle issues (does the assignment create a deep copy or a shallow copy?) making it is easy to break the encapsulation. This question is explored in the thread by @aradi -Should we avoid assignment of derived types in robust programs?

The next solution would be to replace the creator function with a creator subroutine:

call new_t_of_size(5,my_t)

This way we avoid inadvertently triggering the finalizer during creation.

IMO, this issue is addressed poorly in Fortran textbooks, the exception being Scientific Software Design by @rouson, Xia, and Xu. A couple of older references which describe the issue are,