How to free memory associated with c_ptr

I am trying to use c_ptr and c_f_pointer to return an unknown amount of data from a C function, The task is to return the perfect squares (1, 4, 9, etc.) up to some maximum.

For the C code

#include <stdlib.h>

int *squares_p(const int nsq_max, const int sq_max, int *nsq) {
	// return up to nsq_max squares, not exceeding sq_max
	// nsq = # of squares returned
	int* ptr;
	// allocate memory for nsq_max integers
	ptr = (int*)malloc(nsq_max*sizeof(int));
	*nsq = nsq_max;
	int j;
	for (int i = 0; i < nsq_max; ++i) {
		j = i+1;
		ptr[i] = j*j;
		if (ptr[i] > sq_max) {
			*nsq = i;
		        // reallocate if fewer than nsq_max integers are
		        // returned
			ptr = (int *) realloc(ptr,*nsq);
			break;
		}
	}
	return ptr;
}

int nsquares(const int nsq_max, const int sq_max, int squares[nsq_max]) {
	// return up to nsq_max squares, not exceeding sq_max
	// nsq = # of squares returned
	int nsq = nsq_max, j;
	for (int i = 0; i < nsq_max; ++i) {
		j = i+1;
		squares[i] = j*j;
		if (squares[i] > sq_max) {
			nsq = i;
			break;
		}
	}
	return nsq;
}

compiling and linking with the Fortran code below on WSL2 with ifort -g -traceback

program x_c_f_pointer
use iso_c_binding, only : c_ptr, c_f_pointer, c_int
implicit none
type(c_ptr) :: c_p
integer(c_int), pointer :: f_ip(:) => null()
integer :: nsq
interface
!
function squares_p(nsq_max, sq_max, nsq) bind(c)
import c_ptr, c_int
integer(kind=c_int), value, intent(in)  :: nsq_max ! max # of squares to return
integer(kind=c_int), value, intent(in)  :: sq_max  ! max value of squares to return
integer(kind=c_int)       , intent(out) :: nsq     ! # of squares returned
type(c_ptr) :: squares_p ! pointer to squares returned
end function squares_p
!
end interface
integer :: sq_max
integer, parameter :: nsq_max = 10
print "(*(a6))","sq_max","#sq","f_ip"
do sq_max=0,5
   c_p = squares_p(nsq_max,sq_max,nsq)
   call c_f_pointer(c_p,f_ip,[nsq]) ! copy c_p to f_ip
   print "(*(i6))",sq_max,nsq,f_ip
   if (associated(f_ip)) deallocate (f_ip)
end do
end program x_c_f_pointer

and running gives the run-time error

sq_max   #sq  f_ip
     0     0
forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated
Image              PC                Routine            Line        Source             
a.out              000000000040CA81  Unknown               Unknown  Unknown
a.out              0000000000403E9B  MAIN__                     25  c_f_pointer.f90
a.out              00000000004037E2  Unknown               Unknown  Unknown
libc-2.31.so       00007FA974FDF0B3  __libc_start_main     Unknown  Unknown
a.out              00000000004036EE  Unknown               Unknown  Unknown

In a similar case discussed at the Intel Fortran forum, @sblionel said

You must not DEALLOCATE a pointer that wasn’t allocated through Fortran ALLOCATE. (This could be through a call to CFI_allocate when using a C descriptor in C, but you’re not doing that.) Furthermore, the pointer you get with C_F_POINTER is generally not valid for use with DEALLOCATE

I can remove the deallocate from the Fortran code, but I think the C code needs to be fixed so that the memory allocated in the function int *squares_p() is freed, and I don’t know where to do that.

When I avoid pointers and call the C function nsquares with

Fortran code
module m
use iso_c_binding, only: c_int
implicit none
interface
!
function nsquares(nsq_max, sq_max, squares) bind(c)
import c_int
integer(kind=c_int), intent(in), value :: nsq_max, sq_max
integer(kind=c_int), intent(out) :: squares(nsq_max)
integer(kind=c_int) :: nsquares
end function nsquares
!
end interface
contains
function squares(nsq_max,sq_max) result(sq) ! wrapper for nsquares
integer, intent(in)  :: nsq_max ! max # of squares to return
integer, intent(in)  :: sq_max  ! max value of squares to return
integer, allocatable :: sq(:)
integer              :: nsq
allocate (sq(nsq_max))
nsq = nsquares(nsq_max, sq_max, sq)
if (nsq < nsq_max) sq = sq(:nsq)
end function squares
end module m
!
program main
use m, only: c_int, squares
implicit none
integer, parameter :: nsq_max = 1000
integer(kind=c_int) :: sq_max
integer(kind=c_int), allocatable :: sq(:)
print "(*(a6))","sq_max","#sq","sq"
do sq_max=0,5
   sq = squares(nsq_max,sq_max)
   print "(*(i6))",sq_max,size(sq),sq
end do
end program main

the program works, giving output

sq_max   #sq    sq
     0     0
     1     1     1
     2     1     1
     3     1     1
     4     2     1     4
     5     2     1     4
2 Likes

In gtk-fortran, we use functions declared on the C side like g_free() or g_list_free().

The C library must offer that kind of functions for language bindings.

2 Likes

Try making an interface to C free function

  Interface  ! interface to C free function.

    Subroutine c_free(ptr) BIND(C,name="free")
      IMPORT :: C_PTR
      Implicit NONE
      Type(C_PTR), VALUE :: ptr
    End Subroutine c_free

  End Interface

Use c_free to free the memory associated with the ptr returned from C (assuming the associated memory was allocated in the C function). Also, I like to prefix the c_ to the C function name to remind me I’m calling a C function and not Fortran.

Edit. This will work with C malloc ptrs but I’m not sure if the memory was allocated using C++ new what happens

4 Likes

Thanks, that works. For the code

program x_c_f_pointer
use iso_c_binding, only : c_ptr, c_f_pointer, c_int
implicit none
type(c_ptr) :: c_p
integer(c_int), pointer :: f_ip(:) => null()
integer :: nsq
interface
!
function squares_p(nsq_max, sq_max, nsq) bind(c)
import c_ptr, c_int
integer(kind=c_int), value, intent(in)  :: nsq_max ! max # of squares to return
integer(kind=c_int), value, intent(in)  :: sq_max  ! max value of squares to return
integer(kind=c_int)       , intent(out) :: nsq     ! # of squares returned
type(c_ptr) :: squares_p ! pointer to squares returned
end function squares_p
!
subroutine c_free(ptr) bind(c,name="free")
import c_ptr
type(c_ptr), value :: ptr
end subroutine c_free
!
end interface
integer :: sq_max
integer, parameter :: nsq_max = 10
print "(*(a6))","sq_max","#sq","f_ip"
do sq_max=0,5
   c_p = squares_p(nsq_max,sq_max,nsq)
   call c_f_pointer(c_p,f_ip,[nsq]) ! copy c_p to f_ip
   print "(*(i6))",sq_max,nsq,f_ip
   call c_free(c_p)
end do
end program x_c_f_pointer

compiled and linked with the C code shown earlier, valgrind ./a.out says

All heap blocks were freed -- no leaks are possible

If the the call to c_free is commented out valgrind ./a.out says

==1796== LEAK SUMMARY:
==1796==    definitely lost: 5 bytes in 4 blocks
2 Likes

Glad that works for you. Also, just to be safe I would also nullify f_ip just prior to calling c_free.

2 Likes

How should Fortran call a C++ function returning vector <int> ? I came up with

squares.cpp

#include <stdlib.h>
#include <vector>
using namespace std;

extern "C" {
	int *squares_p(const int nsq_max, const int sq_max, int *nsq);
}

vector <int> squares_vec(const int nsq_max, const int sq_max) {
	vector <int> v;
	for (int i=1; i<=nsq_max; i++) {
		const int j = i*i;
		if (j > sq_max) break;
		v.push_back(j);
	}
	return v;
}

int *vec_to_pointer(const vector <int> & w, int *n) {
	*n = w.size();
	int* ptr = new int[*n];
	std::copy(w.begin(), w.end(), ptr);
	return ptr;
}

int *squares_p(const int nsq_max, const int sq_max, int *nsq) {
	// return up to nsq_max squares, not exceeding sq_max
	// nsq = # of squares returned
	const vector <int> squares = squares_vec(nsq_max, sq_max);
	*nsq = squares.size();
	return vec_to_pointer(squares, nsq);
}

called by

xwrap_c_f_pointer.f90
module squares_mod
use iso_c_binding, only : c_ptr, c_f_pointer, c_int
implicit none
interface
!
function squares_p(nsq_max, sq_max, nsq) bind(c)
import c_ptr, c_int
integer(kind=c_int), value, intent(in)  :: nsq_max ! max # of squares to return
integer(kind=c_int), value, intent(in)  :: sq_max  ! max value of squares to return
integer(kind=c_int)       , intent(out) :: nsq     ! # of squares returned
type(c_ptr)                             :: squares_p ! pointer to squares returned
end function squares_p
!
subroutine c_free(ptr) bind(c,name="free")
import c_ptr
type(c_ptr), value :: ptr
end subroutine c_free
!
end interface
contains
function squares(nsq_max, sq_max) result(sq_vec)
! return up to nsq_max squares with values up to sq_max
integer(kind=c_int), value, intent(in)  :: nsq_max ! max # of squares to return
integer(kind=c_int), value, intent(in)  :: sq_max  ! max value of squares to return
integer(kind=c_int), allocatable        :: sq_vec(:)
integer(kind=c_int)                     :: nsq
type(c_ptr)                             :: c_p
integer(c_int)     , pointer            :: f_ip(:) => null()
c_p = squares_p(nsq_max,sq_max,nsq)
call c_f_pointer(c_p,f_ip,[nsq]) ! copy c_p to f_ip
sq_vec = f_ip
call c_free(c_p) ! free memory associated with c_p to avoid memory leak
end function squares
end module squares_mod
!
program main
use squares_mod, only: c_int, squares
implicit none
integer(kind=c_int) :: sq_max
integer(kind=c_int), parameter :: nsq_max = 10
integer, allocatable :: sq_vec(:)
print "(*(a6))","sq_max","#sq","f_ip"
do sq_max=0,5
   sq_vec = squares(nsq_max, sq_max)
   print "(*(i6))", sq_max, size(sq_vec), sq_vec
end do
deallocate (sq_vec)
end program main

compiled with

g++ -o squares.o -c squares.cpp
gfortran squares.o xwrap_c_f_pointer.f90 -lstdc++

which gives the same output as the previous program, with the C++ code being simpler than the analogous C code.

Since vector is the most important and widely used C++ container, would it be possible to have the language make it interoperate with a 1D Fortran allocatable array?

The last time I looked allocatable arrays are not directly interoperable with C pointers. I think you might be able to use the ISO_Fortran_binding.h descriptors on the C side to make them interoperable but don’t quote me on that. I haven’t studied the ISO_Fortran_binding.h stuff enough to know what is (or isn’t) possible. You might look at the SWIG-Fortran bindings from ORNL to see if they support vector classes.

See

and

It depends what you are trying to achieve. Your current solution is making two copies, one in vec_to_pointer which copies from a C++ vector to a regular C array, and a second copy in the Fortran glue code. This doesn’t make a lot of sense.

The options I would consider instead are

  1. Keep a reference to the C++ vector as a void * in Fortran (potentially within a derived type), and establish a “view” of the vector using a Fortran pointer array. The C++ vector needs to be de-allocated manually once it’s not required anymore.
  2. Copy the values from the C++ vector into a Fortran array, using either
    a. an “over-sized” array of size nsq_max, of which only the first nsq values are valid.
    b. a Fortran array descriptor from "ISO_Fortran_binding.h" to establish an allocatable array of the correct size from C/C++

Now I realize this is just an exercise, but the size of the array required can be calculated from the square root of sq_max. Hence you could actually pre-allocate the Fortran array of the right size, and manipulate it in C++ as an std::span.

Edit: I’ve appended a demonstration for how 2a might look.

// squares.cpp
#include <algorithm>
#include <iostream>
#include <vector>
#include <utility>

int squares_vec(int nsq_max, int sq_max, std::vector<int> &v) {
    
    std::vector<int> w; // empty container
    w.reserve(nsq_max); // reserve space for up to nsq_max elements

    for (int i = 1; i <= nsq_max; i++) {
        auto sq = i*i;
        if (sq > sq_max) break;
        w.push_back(sq);
    }

    w.shrink_to_fit(); // optional
    v = std::move(w);

    return v.size();
}

extern "C" {

// Calculate positive squares smaller than or equal to sq_max
//
// Inputs:
//     nsq_max - maximum number of squares returned
//     sq_max - the largest square possibly returned
//     arr - an integer array of size nsq_max, 
//.          on output contains the squares
//
// Returns: the number of squares that meet the conditions
// 
int c_squares_vec(int nsq_max, int sq_max, int arr[]) {
    std::vector<int> v; // empty vector upon entry, automatically destroyed upon exit
    int nsq = squares_vec( nsq_max, sq_max, v);
    std::copy( v.begin(), v.end(), arr);
    return nsq;
}

}
1 Like