Say I have a derived type which owns a C array. The purpose of doing this is to guarantee the C memory will be suitably finalized. Below are my C memory management routines and the Fortan wrapper:
// resource.c
#include "stdlib.h"
#include <stdio.h>
double* allocate_resource(int n) {
double* ptr;
/* Array of n doubles. */
ptr = malloc(n * sizeof(double));
return ptr;
}
void free_resource(double* ptr) {
free(ptr);
}
! main.f90
module test
use, intrinsic :: iso_c_binding
implicit none
private
integer, parameter, public :: dp = c_double
public :: assign_resource
public :: resource_owner
type :: resource_owner
type(c_ptr) :: ptr = c_null_ptr
real(c_double), pointer :: a(:) => null()
contains
procedure :: print
final :: finalize
end type
!
! C routines that allocate and free memory (resource.c)
!
interface
function allocate_resource(n) bind(c,name="allocate_resource")
import c_int, c_ptr
integer(c_int), intent(in), value :: n
type(c_ptr) :: allocate_resource
end function
subroutine free_resource(ptr) bind(c,name="free_resource")
import c_ptr
type(c_ptr), intent(in), value :: ptr
end subroutine
end interface
contains
subroutine assign_resource(owner,n)
type(resource_owner), intent(out) :: owner
integer(c_int), intent(in) :: n
print *, "initialize(owner,n)"
owner%ptr = allocate_resource(n)
call c_f_pointer(owner%ptr, owner%a, [n])
if (.not. associated(owner%a)) then
print *, "Resource allocation failed"
stop
end if
end subroutine
subroutine print(this)
class(resource_owner), intent(in) :: this
print*, "print(this)"
print*, this%a
end subroutine
subroutine finalize(this)
type(resource_owner) :: this
print *, "finalize(this)"
if (associated(this%a)) then
nullify(this%a)
call free_resource(this%ptr)
this%ptr = c_null_ptr
end if
end subroutine
end module
program main
use test
implicit none
type(resource_owner) :: owner
call assign_resource(owner,4)
owner%a = [real(dp) :: 1.0, 2.0, 3.0, 4.0]
call owner%print()
! owner is not finalized automatically in main program block
end program
Compiling is done with the commands:
gcc -c resource.c
gfortran -o main main.f90 resource.o
What I see as output is
>main.exe
finalize(this)
initialize(owner,n)
print(this)
1.0000000000000000 2.0000000000000000 3.0000000000000000 4.0000000000000000
I would expect another call to finalize, just before the program exits. Is it acceptable to leave the C memory not freed?
A simple solution exists, which is to place everything in the main program block into a subroutine:
program main
call main_with_finalization()
contains
subroutine main_with_finalization()
use test
implicit none
type(resource_owner) :: owner
call assign_resource(owner,4)
owner%a = [real(dp) :: 1.0, 2.0, 3.0, 4.0]
call owner%print()
end subroutine
end program
With this modification I can see two calls to finalize in the output, giving me the assurance that the C memory has been freed.
This brings me to two questions:
- Why is the behavior of the main program unit with respect to finalization different from subprograms?
- Should placing the “driver” code in a subprogram be considered best practice?