Fortran bindings to C function that creates arrays of strings

Hello,

I am writing some Fortran bindings to a C library that I wrote, which itself builds upon HDF5 to create a file format for dynamics simulations. In particular, I have functions that produce an array of strings with the following prototype (see below for an example implementation):

int c_array_processing(my_type *a, int n, char **result);

Here my_type is a struct holding info about the file I am reading, n is the number of elements in the array I want, and results is the array created by the function. The C function is written so that it should be used in the following way:

my_type *a = ...;
int n = 2; // for instance
char *values[n];
int res =  c_array_processing(a, n, values);

I have tested it, and it works as expected. Now I have the written the following Fortran interface:

interface
     integer(kind=c_int) function f90_array_processing(a, n, result) bind(C, name="c_array_processing")
       use iso_c_binding, only: c_int, c_ptr
       integer(kind=c_int), value, intent(in) :: a
       integer(kind=c_int), value, intent(in) :: n
       type(c_ptr), intent(out) :: result
     end function f90_array_processing
  end interface

and my problem is that the value of n changes after the call to the function…

This minimal example shows the problems I have, with a C function c_array_processing that does roughly what the function in the real library is doing:

lib.c:

#include <stdio.h>
#include <stdlib.h>
#include <string.h>

int c_array_processing(int *a, int n, char **test) {
  printf("n in C (start) is %d\n", n);
  printf("n in C (before loop) is %d\n", n);
  for (int i=0; i<n; i++) {
    test[i] = malloc( sizeof(char *) * 255);
    test[i][0] = '\0';
    strncat(test[i], "Test", strlen("Test")+1);
  }
  printf("n in C (after loop) is %d\n", n);
  return 0;
}

int c_no_array(int *a, int n) {
  printf("n in C is %d\n", n);
  return 0;
}

prog.f90:

program test
  use iso_c_binding, only: c_int, c_ptr
  implicit none

  interface
     integer(kind=c_int) function f90_array_processing(a, n, test) bind(C, name="c_array_processing")
       use iso_c_binding, only: c_int, c_ptr
       integer(kind=c_int), intent(in) :: a
       integer(kind=c_int), value, intent(in) :: n
       type(c_ptr), intent(out) :: test
     end function f90_array_processing
  end interface

  interface
     integer(kind=c_int) function f90_no_array(a, n) bind(C, name="c_no_array")
       use iso_c_binding, only: c_int, c_ptr
       integer(kind=c_int), intent(in) :: a
       integer(kind=c_int), value, intent(in) :: n
     end function f90_no_array
  end interface

  print '(A)', 'Printing return value of functions'
  print '(A)', '=================================='
  call test_routine_print_res()
  print *, ''

  print '(A)', 'Not printing return value of functions'
  print '(A)', '======================================'
  call test_routine_no_res()

contains
  
  subroutine test_routine_print_res()
    integer(kind=c_int) :: a, res
    integer(kind=c_int) :: n
    type(c_ptr) :: test

    a = 10
    n = 2

    print '(A,I0)', 'F90 START: n = ', n
    print '(A)', '  * Calling f90_array_processing'
    res = f90_array_processing(a, n, test)
    print '(A)',    '  * After call:'
    print '(A,I0)', '    res = ', res
    print '(A,I0)', '    n   = ', n

    print '(A)', '  * Calling f90_no_array'
    res = f90_no_array(a, n)
    print '(A)',    '  * After call:'
    print '(A,I0)', '    res = ', res
    print '(A,I0)', '    n   = ', n
  end subroutine test_routine_print_res


  subroutine test_routine_no_res()
    integer(kind=c_int) :: a, res, res2
    integer(kind=c_int) :: n
    type(c_ptr) :: test

    a = 10
    n = 2

    print '(A,I0)', 'F90 START: n = ', n
    print '(A)', '  * Calling f90_array_processing'
    res = f90_array_processing(a, n, test)
    print '(A)',    '  * After call:'
    print '(A,I0)', '    n   = ', n

    print '(A)', '  * Calling f90_no_array'
    res = f90_no_array(a, n)
    print '(A)',    '  * After call:'
    print '(A,I0)', '    n   = ', n
  end subroutine test_routine_no_res
  
end program test

Makefile:

SRC_f90=prog.f90 
SRC_C=lib.c
OBJ=prog.o lib.o

all: test_f90

test_f90: c_lib f90_prog
	gfortran -o $@ $(OBJ)

f90_prog: prog.f90
	gfortran -c -O0 $<

c_lib: lib.c
	gcc -c -O0 $<

clean:
	find . -name "*.o" -delete
	find . -name "*.mod" -delete

.PHONY: clean

Here are the results:

$ ./test_f90
Printing return value of functions
==================================
F90 START: n = 2
  * Calling f90_array_processing
n in C (start) is 2
n in C (before loop) is 2
n in C (after loop) is 2
  * After call:
    res = 0
    n   = 2
  * Calling f90_no_array
n in C is 2
  * After call:
    res = 0
    n   = 2
 
Not printing return value of functions
======================================
F90 START: n = 2
  * Calling f90_array_processing
n in C (start) is 2
n in C (before loop) is 2
n in C (after loop) is 2
  * After call:
    n   = 25745
  * Calling f90_no_array
n in C is 25745
  * After call:
    n   = 25745

As you can see, in the second case, the value of n is changing, and I cannot see why. I suppose that must have something to do with the string array allocations in the C function, but I am a bit lost here…

I have full control over the C library, so I can modify it to have a better interface !

Thanks a lot for your help !

And if you remove the value attribute for n, is the problem still present?

Thanks for your answer !

If I remove value the problem disappears indeed, and n keeps its original value all the time:

Printing return value of functions
==================================
F90 START: n = 2
  * Calling f90_array_processing
n in C (start) is -1155080312
n in C (before loop) is -1155080312
n in C (after loop) is -1155080312
  * After call:
    res = 0
    n   = 2
  * Calling f90_no_array
n in C is -1155080312
  * After call:
    res = 0
    n   = 2
 
Not printing return value of functions
======================================
F90 START: n = 2
  * Calling f90_array_processing
n in C (start) is -1155080316
n in C (before loop) is -1155080316
n in C (after loop) is -1155080316
  * After call:
    n   = 2
  * Calling f90_no_array
n in C is -1155080316
  * After call:
    n   = 2

I’m experimenting in this direction, replacing int n by int *n in the prototype:

int c_array_processing(int *a, int *n, char **test) {
  printf("n in C (start) is %d\n", *n);
  printf("n in C (before loop) is %d\n", *n);

  for (int i=0; i<*n; i++) {
    printf("BEFORE: i = %d, n = %d\n", i, *n);
    test[i] = malloc( sizeof(char *) * 256);
    test[i][0] = '\0';
    strncat(test[i], "Test", strlen("Test")+1);
    printf("AFTER: i = %d, n = %d\n", i, *n);
  }

  for (int i=0; i<*n; i++) {
    printf("%s ", test[i]);
  }
  printf("\n");
  printf("n in C (after loop) is %d\n", *n);
  return 0;
}

I added prints of the values of i and n in the loop, and that’s interesting:

Not printing return value of functions
======================================
F90 START: n = 2
  * Calling f90_array_processing
n in C (start) is 2
n in C (before loop) is 2
BEFORE: i = 0, n = 2
AFTER: i = 0, n = 2
BEFORE: i = 1, n = 2
AFTER: i = 1, n = 1752500784
BEFORE: i = 2, n = 1752500784
AFTER: i = 2, n = 1752500784
BEFORE: i = 3, n = 1752500784
AFTER: i = 3, n = 1752500784
BEFORE: i = 4, n = 1752500784
AFTER: i = 4, n = 1752500784
BEFORE: i = 5, n = 1752500784
...
Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

There is definitely something going on with the strncat in the loop, I think I mess up the memory somehow…

I think I found the solution: the c_ptr I use in res = f90_array_processing(a, n, test) is not defined at this point, while the C code expects to be able to malloc the members of the test array…

The proper way to do this, it seems (and keeping passing n as value), is to do the following:

lib.c:

int c_array_processing(int *a, int n, char **test) {
  for (int i=0; i<n; i++) {
    test[i] = malloc( sizeof(char *) * 256);
    test[i][0] = '\0';
    strncat(test[i], "Test", strlen("Test")+1);
  }

  printf("Written by the C function:\n");
  for (int i=0; i<n; i++) {
    printf("%s\n", test[i]);
  }
  return 0;
}

prog.f90:

program test
  use iso_c_binding, only: c_int, c_ptr, c_char, c_f_pointer
  implicit none

  interface
     integer(kind=c_int) function f90_array_processing(a, n, test) bind(C, name="c_array_processing")
       use iso_c_binding, only: c_int, c_ptr
       integer(kind=c_int), intent(in) :: a
       integer(kind=c_int), value, intent(in) :: n
       type(c_ptr), intent(inout) :: test(*)
     end function f90_array_processing
  end interface

  call test_routine_no_res()

contains
    subroutine test_routine_no_res()
    integer(kind=c_int) :: a, res, res2
    integer(kind=c_int) :: n
    type(c_ptr), allocatable :: test(:)
    character(kind=c_char), pointer :: fptr(:) => null()
    integer :: i, lenstr
    character(len=256), allocatable :: authors(:)

    a = 10
    n = 2

    print '(A,I0)', 'F90 START: n = ', n
    print '(A)', '  * Calling f90_array_processing'
    allocate(test(n))
    allocate(authors(n))
    res = f90_array_processing(a, n, test)

    do i=1, n
       call c_f_pointer( test(i), fptr, [256] )
       lenstr = cstrlen(fptr(:))
       authors(i) = transfer(fptr(1:lenstr), authors(i))
  
    end do

    print *, 'Recovered by Fortran:'
    do i=1, n
       print *, trim(authors(i))
    end do
  end subroutine test_routine_no_res


  function cstrlen(str) result(res)
    !! Calculate the length of a C string.
    !!
    use iso_c_binding, only: C_NULL_CHAR, c_char
    character(kind=c_char), intent(in) :: str(:)

    integer :: res

    integer :: i

    do i=1, size(str)
       if (str(i) == c_null_char) then
          res = i - 1
          return
       end if
    end do
    res = i
  end function cstrlen
end program test

Now with n =4 :

F90 START: n = 4
  * Calling f90_array_processing
Written by the C function:
Test
Test
Test
Test
 Recovered by Fortran:
 Test
 Test
 Test
 Test
2 Likes