I have create a more complete example. Let’s assume a C function which returns a string representation of an integer:
// int2str.c
#include <stdio.h>
#include <stdlib.h>
char *int2str(int i) {
int length = snprintf( NULL, 0, "%d", i );
char* str = malloc( length + 1 );
snprintf( str, length + 1, "%d", i );
return str;
}
This function first determines the length of the the character pointer necessary, before writing the integer value i
to the instance str
.
The next step is defining the Fortran interfaces:
! int2str_mod.f90
module int2str_mod
use, intrinsic :: iso_c_binding
interface
type(c_ptr) function c_int2str(i) bind(c,name="int2str")
import c_int, c_ptr
integer(c_int), value :: i
end function
integer(c_size_t) function c_strlen(s) bind(c,name="strlen")
import c_size_t, c_ptr
type(c_ptr), intent(in), value :: s
end function
subroutine c_free(ptr) bind(c,name="free")
import c_ptr
type(c_ptr), value :: ptr
end subroutine
end interface
As per @FortranFan’s suggestion, this time I am using the C standard library function strlen
to recover the length of the string in C. This function does not count the trailing “\n” character used as the string terminator. Next we write a wrapper function in Fortran:
contains
function int2str(i) result(str)
integer(c_int), intent(in) :: i
character(:,c_char), allocatable :: str
type(c_ptr) :: cstr
integer(c_size_t) :: n
cstr = c_int2str(i)
n = c_strlen(cstr)
allocate(character(len=n,kind=c_char) :: str)
block
character(len=n,kind=c_char), pointer :: s
call c_f_pointer(cstr,s) ! Recovers a view of the C string
str = s ! Copies the string contents
end block
call c_free(cstr)
end function
end module
We can use the c_strlen
function to correctly allocate both the return value str
and the temporary buffer within the block
section. After running the code in my previous reply through valgrind
I was surprised to find out it created a memory leak! It looks like for the C function defined above it is necessary to free the memory explicitly. This is done by calling the void free(void * ptr)
function.
A short example program:
! main.f90
program main
use int2str_mod
print *, int2str(11_c_int), len(int2str(11_c_int))
print *, int2str(121_c_int), len(int2str(121_c_int))
print *, int2str(1221_c_int), len(int2str(1221_c_int))
end program
Compiling and running the program:
$ gfortran -Wall -ggdb3 int2str.c int2str_mod.f90 main.f90
$ ./a.out
11 2
121 3
1221 4
Output with valgrind
:
$ valgrind --leak-check=full ./a.out
==30654== Memcheck, a memory error detector
==30654== Copyright (C) 2002-2017, and GNU GPL'd, by Julian Seward et al.
==30654== Using Valgrind-3.13.0 and LibVEX; rerun with -h for copyright info
==30654== Command: ./a.out
==30654==
11 2
121 3
1221 4
==30654==
==30654== HEAP SUMMARY:
==30654== in use at exit: 0 bytes in 0 blocks
==30654== total heap usage: 33 allocs, 33 frees, 13,626 bytes allocated
==30654==
==30654== All heap blocks were freed -- no leaks are possible
==30654==
==30654== For counts of detected and suppressed errors, rerun with: -v
==30654== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 0 from 0)
Edit: Removed an unneccesary call to c_strlen
.