When making bind(c)
interfaces that includes strings, the common advice is to make a copy of the string with c_null_char
appended to its end. Something like this:
pure function to_c_chars(fchars) result(cchars)
use iso_c_binding, only: c_null_char, c_char
character(len=*), intent(in) :: fchars
character(len=1, kind=c_char), allocatable :: cchars(:)
integer :: i
integer :: n
n = len(fchars)
allocate(cchars(n + 1))
do i = 1, n
cchars(i) = fchars(i:i)
end do
cchars(n + 1) = c_null_char
end function
For many applications this is probably ok because the amount of data copied usually isn’t that much.
I don’t like copying data for no good reason though so recently I’ve been testing an alternative approach and I think I found a neat little trick that will work in a subset of cases. See example below. The limitations are:
- It’s mainly for read-only strings (though you can probably modify it if you’re careful)
- A C++ compiler is required and the
std::string_view
class must be used. This has many of the same features as a regularstd:string
except for mutation though so you can still do quite a bit with it.
My question is: Can anyone see any situations where this will be invalid or do you think it is safe to use?
Fortran interface code (echo.f90):
module echo_mod
use iso_c_binding, only: c_loc
implicit none
private
public echo
interface
subroutine echo_c(chars, n) bind(c)
use iso_c_binding, only: c_ptr, c_int
type(c_ptr), value, intent(in) :: chars
integer(c_int), intent(in) :: n
end subroutine
end interface
contains
subroutine echo(chars)
character(len=*), target, intent(in) :: chars
write(*,*) 'Printing from C: ' // chars
call echo_c(c_loc(chars), len(chars))
end subroutine
end module
C++ code (echo.cpp):
#include <string_view>
#include <iostream>
extern "C" {
void echo_c(const char* chars, const int* n)
{
auto view = std::string_view(chars).substr(0, *n);
std::cout << view << std::endl;
}
}
Usage (main.f90):
program main
use echo_mod, only: echo
implicit none
call echo('Hello world')
end program
Output:
Printing from C: Hello world
Hello world