I have a C function that needs to allocate and fill in a character string. The C program, hello.c
, can be simplified to:
#include <ISO_Fortran_binding.h>
#include <stdio.h>
#include <string.h>
#include <assert.h>
void say_hello(CFI_cdesc_t* res) {
assert (res->rank == 1);
assert (res->type & CFI_type_Character == CFI_type_Character);
assert (res->attribute == CFI_attribute_allocatable);
// If already allocated - free
if (res->base_addr) CFI_deallocate(res);
// Message to be written
char message[] = "Hello, world!";
// Allocate to length of string
const CFI_index_t lower_bounds[1] = {1}; // Remember this is Fortran
const CFI_index_t upper_bounds[1] = {strlen(message)};
int ierr = CFI_allocate(res, lower_bounds, upper_bounds, 1);
if (ierr) {
printf("Got error: %d\n", ierr);
return;
}
// Copy string into allocated memory
strncpy((char*)res->base_addr, message, strlen(message));
printf("All good here\n");
}
and the accompanying Fortran driver program is:
PROGRAM main
USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_char
IMPLICIT NONE (type, external)
INTERFACE
! void json_dump(jsoncppc_t* jsonc, CFI_cdesc_t* res, int* ierr)
SUBROUTINE say_hello(res) BIND(C)
IMPORT :: c_char
CHARACTER(kind=c_char, len=1), ALLOCATABLE, INTENT(out) :: res(:)
END SUBROUTINE say_hello
END INTERFACE
CHARACTER(kind=C_CHAR, len=1), ALLOCATABLE :: message(:)
CALL say_hello(message)
WRITE(*, *) message(1:SIZE(message))
END PROGRAM main
This compiles all well and good with GCC and GFortran 11:
gcc-11 -O0 -g -c hello.c && gfortran-11 -g -O0 hello.o program.F90 && ./a.out
and executes as expected.
With GCC and GFortran 12 I get the following error message compiling the above Fortran file:
$ gcc-12 -O0 -g -c hello.c && gfortran-12 -g -O0 hello.o program.F90 && ./a.out
program.F90:7:32:
7 | SUBROUTINE say_hello(res) BIND(C)
| 1
Error: Allocatable character dummy argument ‘res’ at (1) must have deferred length as procedure ‘say_hello’ is BIND(C)
So I go ahead and change the len=1
to len=:
and it compiles great in GFortran 12.3:
PROGRAM main
USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_char
IMPLICIT NONE (type, external)
INTERFACE
! void json_dump(jsoncppc_t* jsonc, CFI_cdesc_t* res, int* ierr)
SUBROUTINE say_hello(res) BIND(C)
IMPORT :: c_char
CHARACTER(kind=c_char, len=:), ALLOCATABLE, INTENT(out) :: res(:)
END SUBROUTINE say_hello
END INTERFACE
CHARACTER(kind=C_CHAR, len=:), ALLOCATABLE :: message(:)
CALL say_hello(message)
WRITE(*, *) message(1:SIZE(message))
END PROGRAM main
However, in GFortran 11.4 I get the following error:
gcc-11 -O0 -g -c hello.c && gfortran-11 -g -O0 hello.o program.F90 && ./a.out
CFI_allocate: Failure in memory allocation.
Got error: 11
Digging deeper into the CFI_cdesc_t
that is received by the C function, I see that the type
member correspond to CFI_type_Character
in this last case. When it is compiled with len=1
on the Fortran side the type is CFI_type_char
. This affects how the memory allocation is done inside CFI_allocate:
/* If the type is a Fortran character type, the descriptor's element
length is replaced by the elem_len argument. */
if (dv->type == CFI_type_char || dv->type == CFI_type_ucs4_char)
dv->elem_len = elem_len;
ref: https://github.com/gcc-mirror/gcc/blob/master/libgfortran/runtime/ISO_Fortran_binding.c
So the failing case with len=:
and GFortran 11 seems to be because the type
is incorrectly set in the C descriptor, elem_len
is unset and the memory allocation fails.
Trying to manually set res->elem_len = 1
before CFI_allocate makes the C function work, but then there is another memory-error in the driver program… I do not bother posting this here.
This became quite long and complicated, so I’ll make a summary with a few questions:
- Have I missed something crucial?
- Am I right if I assume that there is a bug in how GFortran 11 behave here?
- Does anyone see a way to write the code such that it works with both GFortran 11 and 12 simultaneously?
The ifx
from Intel seems to compile both variants without problems.