I do not often have to do serious character processing or C interop, but today I found myself needing both. I want to wrap a C function which takes a char*
argument. I came up with a solution that appears to work, but I am not entirely pleased with it. I wonder if there are features of ISO_C_BINDING that I am missing, or if my approach could be made more robust.
Taking for example the C function
// hello.c
#include <stdio.h>
void hello(char *name) {
printf("Hello, %s\n!", name);
}
I write a Fortran interface using ISO_BIND_C and define a subroutine that wraps the C function in such a way that I can pass in a Fortran character variable.
! wrap_hello.f90
module wrap_hello
implicit none
private
public :: hello
interface
subroutine c_hello(name) bind(C, name="hello")
use iso_c_binding, only: c_char
character(kind=c_char), dimension(*) :: name
end subroutine c_hello
end interface
contains
subroutine hello(name)
use iso_c_binding, only: c_char, c_null_char
character(len=*), intent(in) :: name
character(kind=c_char), dimension(len(name)+1) :: c_name
integer :: i
do i = 1, len(name)
c_name(i) = name(i:i)
end do
c_name(len(name)+1) = c_null_char
call c_hello(c_name)
end subroutine hello
end module wrap_hello
If I use this module in a test program
! test.f90
program test
use wrap_hello, only: hello
implicit none
character(len=100) :: name
read *, name
call hello(trim(name))
end program
It appears to behave as expected. However, there are a few aspects of my implementation that I do not like:
- The conversion from Fortran character variable to C character array is clunky. I feel there must be a better way than explicitly looping and then tacking on a NUL.
- It assumes that assigning a default-kind character to a
character(c_char)
“just works”. In GCC (and probably most compilers), the default character kind andc_char
coincide. Is that mandated by the standard, or am I asking for trouble?
Toward issue #2, when doing C-interop with numerical codes, I usually satisfy myself by doing explicit type conversions to make sure the kinds are exactly right on both the Fortran and C ends. But as far as I know, there’s no analogue for conversion of one character kind to another. Is this paranoia, or is it a real concern if robustness is a priority?
In playing around, I found that instead of having the local variable c_name
, I can get away with just doing call c_hello(name//c_null_char)
, but that seems really fast and loose. It solves issue #1 at the cost of increasing my paranoia toward issue #2.
For completeness, I compiled the example with GCC 9.3 as
$ gcc-9 -c -Wall -Wextra -fsanitize=address -o hello.o hello.c
$ gfortran-9 -c -Wall -Wextra -std=f2018 -pedantic -fsanitize=address -fcheck=all -o hello_wrap.o hello_wrap.f90
$ gfortran-9 -c -Wall -Wextra -std=f2018 -pedantic -fsanitize=address -fcheck=all -o test.o test.f90
$ gfortran-9 -o test hello.o hello_wrap.o test.o -lasan