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