Reputation: 335
This is an extension to my previous post passing a character and double from C++ to Fortran, by mapping the same data structure. It adds an allocatable array. As this is not interop, I have to create two structures on the Fortran side, one that maps to the C++ structure (interop) and another that contains the allocatable array. Then I allocate the internal array "var" and copy from the external version (which maps from the C++ version) to the internal one using a technique recommended here here. This works fine.
However in the previous post here (without the allocatable array) I was told that I have to use BIND(C) on the external structure t_stuff_gef_ext. When I add BIND(C) I get a compiler error: "error #8080: Each component of a derived type with the BIND attribute shall be a nonpointer, nonallocatable data component with interoperable type and type parameters. [P_VAR]"
C Code:
#include <iostream>
#include <cstddef>
#include <vector>
using namespace std;
extern "C" {
struct t_stuff_gef {
char name[256];
double extra;
double* p_var;
};
struct t_stuff {
t_stuff_gef gef;
};
void test2(t_stuff *stuff);
}
int main()
{
t_stuff stuff;
strcpy_s(stuff.gef.name, sizeof(stuff.gef.name), "Teststuff");
stuff.gef.extra = 100.0;
stuff.gef.p_var = new double[2];
stuff.gef.p_var[0] = 123.0;
stuff.gef.p_var[1] = 456.0;
test2(&stuff);
}
Fortran code:
module ftncode_mod
use, intrinsic :: iso_c_binding
implicit none
!--external structure, same as C
type, public :: t_stuff_gef_ext
character(1) :: name(256)
real(8) :: extra
real(8), pointer :: var
end type t_stuff_gef_ext
!--internal structure, to be be populated from the interface structure above
type, public :: t_stuff_gef
character(1) :: name(256)
real(8) :: extra
real(8), allocatable :: var(:)
end type t_stuff_gef
type, public :: t_stuff_ext
type(t_stuff_gef_ext) :: gef
end type t_stuff_ext
contains
subroutine test2(stuff_ext) bind(C)
!DEC$ATTRIBUTES DLLEXPORT :: test2
type(t_stuff_ext), target, intent(in) :: stuff_ext
type(t_stuff_gef) :: stuff_gef
integer :: i
real(8) :: k
pointer (p_k,k)
p_k = loc(stuff_ext%gef%var)
allocate(stuff_gef%var(2))
do i = 1, 2
stuff_gef%var(i) = k
p_k = p_k + sizeof(k)
enddo
print *, stuff_gef%var(1)
print *, stuff_gef%var(2)
return
end
end module
Upvotes: 1
Views: 398
Reputation: 2688
I am posting a solution inspired by ivanpribec answer in this discussion: https://fortran-lang.discourse.group/t/allocate-interoperability-and-c-descriptors/5088/5
Context: we have an existing Fortran library that we don't want to modify, with some allocatable arrays in derived types, and we want to access the allocatable arrays from C, without data duplication. The idea is to write wrappers and leave the original library untouched :
! ORIGINAL LIBRARY
module ftncode
implicit none
integer, parameter :: dp = kind(1d0)
type :: t_stuff_gef
character(len=256) :: name
real(dp) :: extra
real(dp), allocatable :: var(:)
end type t_stuff_gef
type :: t_stuff
type(t_stuff_gef) :: gef
end type t_stuff
contains
subroutine test2(stuff)
type(t_stuff), intent(in) :: stuff
integer :: i
print *, stuff%gef%name
print *, stuff%gef%extra
do i = 1, size(stuff%gef%var)
print *, stuff%gef%var(i)
end do
end
end module
! WRAPPER MODULE
module ftncode_wrap
use ISO_C_BINDING
use ftncode
implicit none
contains
type(c_ptr) function stuff_create(n) bind(C)
integer(c_int), intent(in), value :: n
type(t_stuff), pointer :: p
allocate(p)
allocate(p%gef%var(n))
stuff_create = c_loc(p)
end function
subroutine stuff_setname(pc,cstring) bind(C)
type(c_ptr), intent(in), value :: pc
character(kind=c_char,len=1), intent(in) :: cstring(256)
integer :: i
type(t_stuff), pointer :: p
call c_f_pointer(pc,p)
do i = 1, 256
p%gef%name(i:i) = cstring(i)
end do
end subroutine
subroutine stuff_setextra(pc,extra) bind(C)
type(c_ptr) , intent(in), value :: pc
real(c_double), intent(in), value :: extra
type(t_stuff), pointer :: p
call c_f_pointer(pc,p)
p%gef%extra = extra
end subroutine
type(c_ptr) function stuff_getvar(pc) bind(C)
type(c_ptr), intent(in), value :: pc
type(t_stuff), pointer :: p
call c_f_pointer(pc,p)
stuff_getvar = c_loc(p%gef%var)
end function
subroutine stuff_test2(pc) bind(C)
type(c_ptr), intent(in), value :: pc
type(t_stuff), pointer :: p
call c_f_pointer(pc,p)
call test2(p)
end subroutine
subroutine stuff_free(pc) bind(C)
type(c_ptr), intent(inout) :: pc
type(t_stuff), pointer :: p
call c_f_pointer(pc,p)
deallocate( p%gef%var )
deallocate( p )
pc = c_null_ptr
end subroutine
end module
C code:
#include <string.h>
#include <stdlib.h>
#include <stdio.h>
void* stuff_create(int n);
void stuff_setname(void* pc, char* cstring);
void stuff_setextra(void* pc,double extra);
void* stuff_getvar(void* pc);
void stuff_test2(void* pc);
void stuff_free(void** pc);
int main()
{
char name[256];
strncpy(name, "Teststuff",256);
void* stuff = stuff_create(3);
stuff_setname(stuff,name);
stuff_setextra(stuff,100.0);
double* var = (double*)stuff_getvar(stuff);
var[0] = 123.0;
var[1] = 456.0;
var[2] = 789.0;
stuff_test2(stuff);
stuff_free(&stuff);
}
The output is as expected:
% gfortran -c interop2f.f90 && gcc interop2c.c interop2f.o -lgfortran && ./a.out
Teststuff
100.00000000000000
123.00000000000000
456.00000000000000
789.00000000000000
Upvotes: 3
Reputation: 2688
Since the Fortran 2018 standard, allocatable arrays are interopable with C, but this requires more complex stuff on the C side. The underlying question here is "do you really need to equivalence an allocatable array with the C side"? In your case (calling Fortran from C) this would be useful if you were allocating the array on the Fortran side, which is not what you are doing. Otherwise passing simple arrays is simpler, and enough.
Also, in the previous questions/answers you have been told to declare the interoperable variables with the interoperable types (real(c_double)
instead of real(8)
...).
Last, you are using the so-called "Cray pointers", which is a non-standard extension to Fortran that was very popular in the past. Although widely supported, there is no reason to continue using them in new code, as standard modern Fortran has everything needed in terms of pointers.
Again, the solution is using c_ptr
, and pass the size of the array (I am using only one structure level).
#include <iostream>
#include <cstddef>
#include <vector>
using namespace std;
extern "C" {
struct t_stuff {
char name[256];
double extra;
double* p_var;
int varsize;
};
void test2(t_stuff *stuff);
}
int main()
{
t_stuff stuff;
strcpy_s(stuff.name, sizeof(stuff.name), "Teststuff");
stuff.extra = 100.0;
stuff.p_var = new double[2];
stuff.varsize = 2;
stuff.p_var[0] = 123.0;
stuff.p_var[1] = 456.0;
test2(&stuff);
}
module ftncode_mod
use, intrinsic :: iso_c_binding
implicit none
!--external structure, same as C
type, public, bind(C) :: t_stuff
character(1) :: name(256)
real(c_double) :: extra
real(c_ptr) :: varptr
integer(c_int) :: varsize
end type t_stuff_gef
contains
subroutine test2(stuff) bind(C)
!DEC$ATTRIBUTES DLLEXPORT :: test2
type(t_stuff), intent(in) :: stuff
! var is a pointer to an array
real(c_double), pointer :: var(:)
integer :: n, i
! convert the C pointer to the Fortran pointer, using the size of the array
n = stuff%varsize
call c_f_pointer(stuff%varptr,var,[n])
do i = 1, n
print *, var(i)
enddo
end
end module
This is even simpler to pass directly the array instead of passing the structure:
...
void test3(double *stuff,int *n);
...
int main()
{
...
test3(stuff.p_var,&stuff.varsize);
}
...
subroutine test3(var,n) bind(C)
integer, intent(in) :: n
real(c_double), intent(in) :: var(n)
integer :: i
do i = 1, n
print *, var(i)
enddo
end
...
Upvotes: 0