I am thinking about how to pass more complicated data from Fortran to C. No specific question, but suggestions are welcome.
The Fortran interface of a C function cannot have allocatable arguments, but Metcalf, Reid, and Cohen (2018) p370 write
A Fortran pointer or allocatable variable, and most Fortran arrays, do not interoperate
directly with any C entity because C does not have quite the same concepts; for example,
unlike a Fortran array pointer, a C array pointer cannot describe a discontiguous array
section. However, this does not prevent such entities being passed to C via argument
association since Fortran compilers already perform copy-in copy-out when this is necessary.
A derived type with allocatable components is not interoperable with C, but one can allocate the components on the Fortran side and pass them to C. They can be accessed and modified there, but not resized. Here is an example with a small derived type.
For xdt_alloc.f90
module m
use iso_c_binding, only: c_int, c_double
implicit none
type :: stuff
real(kind=c_double), allocatable :: x(:), y(:), z(:)
end type stuff
interface
!
pure subroutine vec_product(n, x, y, xy) bind(c)
import c_int, c_double
integer(kind=c_int), intent(in), value :: n
real(kind=c_double), intent(in) :: x(n), y(n)
real(kind=c_double), intent(out) :: xy(n)
end subroutine vec_product
!
end interface
contains
pure subroutine set_z_to_xy(dt)
type(stuff), intent(in out) :: dt
integer :: n
if ((.not. allocated(dt%x)) .or. (.not. allocated(dt%y)) &
.or. (.not. allocated(dt%z))) error stop
n = size(dt%x)
if (size(dt%y) /= n .or. size(dt%z) /= n) error stop
call vec_product(n, dt%x, dt%y, dt%z)
end subroutine set_z_to_xy
end module m
!
program main
use m , only: stuff, set_z_to_xy
use iso_c_binding, only: c_double
implicit none
type(stuff) :: dt
integer, parameter :: n = 3
allocate (dt%x(n), dt%y(n), dt%z(n))
dt%x = real([2,3,4],kind=c_double)
dt%y = real([5,6,7],kind=c_double)
call set_z_to_xy(dt)
print "(*(1x,f0.1))", dt%z ! 10.0 18.0 28.0
end program main
and vec_product.c
void vec_product(const int n, const double x[], const double y[],
double z[]) {
for (int i=0; i<n; i++) {
z[i] = x[i]*y[i];
}
}
compiling with
gcc -o vec_product.o -c vec_product.c
gfortran vec_product.o xdt_alloc.f90
and running gives
10.0 18.0 28.0
Passing data to C in this way could be inconvenient if the derived type has many components. Metcalf et al. p379 say
It is not uncommon for a Fortran library module to have an initialization procedure that
establishes a data structure to hold all the data for a particular problem that is to be solved.
Subsequent calls to other procedures in the module provide data about the problem or receive
data about its solution. The data structure is likely to be of a type that is not interoperable, for
example because it has components that are allocatable arrays.
The procedures c_loc and c_f_pointer have been designed to support this situation.
…
and give an example of their use.