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
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
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
Passing the array in the arguments
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
...
Related
I have the following test C library:
#include <stdlib.h>
struct mystruct {
int a;
double b;
};
struct mystruct *return_array_of_structs(int *size);
struct mystruct *return_array_of_structs(int *size) {
int i;
struct mystruct *ptr;
ptr = malloc(sizeof(struct mystruct)*10);
for(i=0; i<10; i++) {
ptr[i].a = i+1;
ptr[i].b = (i+1)*1.0L;
}
*size=10;
return ptr;
}
And the following module intended to be compiled with f2py:
module test_c_lib
use iso_c_binding
implicit none
type :: t_mystruct
integer :: a
real(8) :: b
end type
contains
subroutine test()
use iso_c_binding
type(c_ptr) :: ret_c_ptr
integer :: length
! Interface to C function
interface
type(c_ptr) function c_return_array_of_structs(a) bind(C, name="return_array_of_structs")
import
integer(c_int) :: a
end function
end interface
! Call C function
ret_c_ptr = c_return_array_of_structs(length)
end subroutine
end module
The following makefile compiles this:
f_mod.so: f_mod.f90 c_lib.o
f2py -c f_mod.f90 c_lib.o -m f_mod
c_lib.o: c_lib.c
gcc -c -fpic c_lib.c -o c_lib.o
I can load the library in Python normally and execute the test() subroutine without problems.
import f_mod
f_mod.test_c_lib.test()
But I do not how to convert ret_c_ptr into an array of derived type t_mystruct that I can normally operate as an array in Fortran. Any hint?
Note: the question is related to iso c bindings and Fortran, not to f2py or its integration with Python.
If you have a C pointer and want to associate a Fortran pointer with the target of that C pointer, you want to use c_f_pointer to do that association. c_f_pointer doesn't (generally) care whether the type is an intrinsic one or not, or scalar or not.
Let's define the Fortran derived type as an interoperable1 one:
type, bind(c) :: t_mystruct
integer(c_int) :: a
real(c_double) :: b
end type
and then have a Fortran pointer array of that type:
type(t_mystruct), pointer :: ptr_f(:)
With ptr_c pointing to a suitable lump of memory we can do the association:
call c_f_pointer(ptr_c, ptr_f, [length])
to make ptr_f an array of shape [length] pointing to the C target.
1 Being interoperable isn't necessary, but it's certainly helpful to be if it can be.
The right answer to this question is the one provided by francescalus above, however I include the complete excerpt of code with the functions exposed by f2py to Python.
f2py will not allow to return numpy arrays of derived types (which would be a numpy vector of a custom dtype), so you need to return individual vectors per field. Also f2py can not return allocatable arrays without explicit size, therefore this function needs to be split into two calls, one to get the length and another one to get the actual array.
While these are clear limitations of f2py this allows to call directly Fortran functions (or C encapsulated functions as in this example) and get numpy arrays as return values.
The code is not optimised as it implies invoking the C function twice, maybe there is the possibility to use sort kind of static variable like in C, so the second invoke would already had computed the values, although I do not know:
if that is possible at all in Fortran
if that is possible within the context of a shared object (which is what f2py creates from the module)
As there is not that many examples around f2py this might be useful for someone:
module test_c_lib
use iso_c_binding
implicit none
type, bind(c) :: t_mystruct
integer(c_int) :: a
real(c_double) :: b
end type
contains
subroutine get_array_len(l)
use iso_c_binding
integer, intent(out) :: l
type(c_ptr) :: ret_c_ptr
integer :: length
! Interface to C function
interface
type(c_ptr) function c_return_array_of_structs(a) bind(C, name="return_array_of_structs")
import
integer(c_int) :: a
end function
end interface
! Call C function
ret_c_ptr = c_return_array_of_structs(length)
l = length
end subroutine
subroutine get_array(l, a, b)
use iso_c_binding
integer, intent(in) :: l
integer, intent(out) :: a(l)
real(8), intent(out) :: b(l)
type(c_ptr) :: ret_c_ptr
type(t_mystruct), pointer :: f_ptr(:)
integer :: length
! Interface to C function
interface
type(c_ptr) function c_return_array_of_structs(a) bind(C, name="return_array_of_structs")
import
integer(c_int) :: a
end function
end interface
! Call C function
ret_c_ptr = c_return_array_of_structs(length)
call c_f_pointer(ret_c_ptr, f_ptr, [length])
a = f_ptr%a
b = f_ptr%b
end subroutine
end module
I have a C function that uses structures. I developed a Fortran Wrapper which calls the C function. Both libraries are built successfully. I have passed the variables form the PSCAD model and run the case. The PSCAD model is throwing the error.
Error Message:
Type Id Component Namespace Description
dll_df FORTRA~1.LIB(dlltestx.obj) : error LNK2019: unresolved external symbol _test_cfun referenced in function _AUX_CFUN
C-Code:
// This is an example of an exported variable
typedef struct _goose_c
{
int in1;
float in2;
}goose_c;
__declspec(dllexport) void test_cfunc(goose_c *V, double *out1)
{
//*out1 = (*V).in1 + (*V).in2;
*out1 = V->in1 + V->in2;
}
Fortran Wrapper Code:
SUBROUTINE AUX_CFUN(ip1, ip2, out1)
use, intrinsic :: iso_c_binding
implicit none
integer, intent(in) :: ip1
real, intent(in) :: ip2
real, intent(out) :: out1
type, bind(C) :: goose_t
integer(c_int) :: in1
real(c_double) :: in2
end type goose_t
type(goose_t) :: goose_f
! Fortran 90 interface to a C procedure
INTERFACE
SUBROUTINE TEST_CFUN (goose_f,out1) bind (C)
use iso_c_binding
import :: goose_t
type(goose_t), intent (in) :: goose_f
real(c_double), intent (out) :: out1
END SUBROUTINE TEST_CFUN
END INTERFACE
goose_f%in1 = ip1
goose_f%in2 = ip2
! call of the C procedure
CALL TEST_CFUN(goose_f,out1)
RETURN
END SUBROUTINE AUX_CFUN
The bind (C) clause in the interface should be completed with the exact (including the correct case) C name of the function you want to interface; so in your example it should read bind (C, name='test_cfunc'). The Fortran name associated to the C function (TEST_CFUN in your example) can be in principle different, it's up to you to decide whether this is a good idea or not, and it is used in your fortran program with the usual fortran rules, so it is case-insensitive.
I have the following C library (in particular the function I am debugging now is pass_by_reference):
#include <stdlib.h>
double multiply_numbers(double a, double b);
double *get_array(double a);
void pass_by_reference(int *a);
double multiply_numbers(double a, double b) {
return a*b;
}
double *get_array(double a) {
double *retval;
int i;
retval = malloc(100*sizeof(a));
for(i=0; i<100; i++) {
retval[i] = i*a;
}
return retval;
}
void pass_by_reference(int *a) {
*a = 8;
}
And I am trying to get this wrapped by a Fortran subroutine named pass_by_reference (to be latter called via f2py in python):
module test_c_lib
use iso_c_binding
implicit none
contains
subroutine multiply(x, y, z)
use iso_c_binding
real(8), intent(in) :: x
real(8), intent(in) :: y
real(8), intent(out) :: z
! Interface to C function
interface
real(c_double) function c_multiply_numbers(a, b) bind(C, name="multiply_numbers")
import
real(c_double), value :: a,b
end function
end interface
! Call C function
z = c_multiply_numbers(x,y)
end subroutine
subroutine get_array(x, z)
use iso_c_binding
real(8), intent(in) :: x
real(8), intent(out) :: z(100)
type(c_ptr) :: ret_c_ptr
real(8), pointer :: f_ptr(:)
! Interface to C function
interface
type(c_ptr) function c_get_array(a) bind(C, name="get_array")
import
real(c_double), value :: a
end function
end interface
! Call C function
ret_c_ptr = c_get_array(x)
call c_f_pointer(ret_c_ptr, f_ptr, [100])
z = f_ptr
end subroutine
subroutine pass_by_reference(z)
use iso_c_binding
integer, intent(out) :: z
! Interface to C function
interface
type(c_null_ptr) function c_pass_by_reference(a) bind(C, name="pass_by_reference")
import
type(c_int), value :: a
end function
end interface
! Call C function
c_pass_by_reference(z)
end subroutine
end module
And the corresponding makefile:
$ cat makefile
f_mod.so: f_mod.f90 c_lib.o
f2py -c f_mod.f90 c_lib.o -m f_mod
c_lib.o: c_lib.c
gcc -c -fpic c_lib.c -o c_lib.o
When trying to get this compiled with f2py I get:
57 | use iso_c_binding
| 2
......
63 | type(c_null_ptr) function c_pass_by_reference(a) bind(C, name="pass_by_reference")
| 1
Error: Type name 'c_null_ptr' at (1) conflicts with previously declared entity at (2), which has the same name
f_mod.f90:65:43:
57 | use iso_c_binding
| 2
......
65 | type(c_int), value :: a
| 1
Error: Type name 'c_int' at (1) conflicts with previously declared entity at (2), which has the same name
f_mod.f90:63:24:
63 | type(c_null_ptr) function c_pass_by_reference(a) bind(C, name="pass_by_reference")
| 1
Error: The type for function 'c_pass_by_reference' at (1) is not accessible
f_mod.f90:63:24: Warning: Implicitly declared BIND(C) variable 'c_pass_by_reference' at (1) may not be C interoperable [-Wc-binding-type]
f_mod.f90:70:35:
70 | c_pass_by_reference(z)
| 1
Error: 'c_pass_by_reference' at (1) is not a variable
f_mod.f90:63:24-71:
63 | type(c_null_ptr) function c_pass_by_reference(a) bind(C, name="pass_by_reference")
| 2 1
Warning: Implicitly declared variable 'a' at (1) may not be C interoperable but it is a dummy argument to the BIND(C) procedure 'c_pass_by_reference' at (2) [-Wc-binding-type]
f_mod.f90:63:24:
63 | type(c_null_ptr) function c_pass_by_reference(a) bind(C, name="pass_by_reference")
| 1
Warning: Implicitly declared BIND(C) function 'c_pass_by_reference' at (1) may not be C interoperable [-Wc-binding-type]
error: Command "/usr/local/bin/gfortran9 -Wall -g -fno-second-underscore -fPIC -O3 -funroll-loops -I/tmp/tmpk7tn1bgi/src.freebsd-12.2-RC1-amd64-3.7 -I/usr/local/lib/python3.7/site-packages/numpy/core/include -I/usr/local/include/python3.7m -c -fPIC f_mod.f90 -o /tmp/tmpk7tn1bgi/f_mod.o -J/tmp/tmpk7tn1bgi/ -I/tmp/tmpk7tn1bgi/" failed with exit status 1
*** Error code 1
I have two questions:
When iso_c_binding is used, and in this particular example, is the variable a passed to pass_by_reference function actually passed by reference or do I have to specify something different in the interface?
Why f2py is reporting Type name 'c_int' at (1) conflicts with previously declared entity at (2), which has the same name?
How do I specify that the C function does not return anything (void)? I have tried to use type(c_null_ptr)
After implementing all the corrections pointed out in the comments this is the encapsulation that works:
module test_c_lib
use iso_c_binding
implicit none
contains
subroutine multiply(x, y, z)
use iso_c_binding
real(8), intent(in) :: x
real(8), intent(in) :: y
real(8), intent(out) :: z
! Interface to C function
interface
real(c_double) function c_multiply_numbers(a, b) bind(C, name="multiply_numbers")
import
real(c_double), value :: a,b
end function
end interface
! Call C function
z = c_multiply_numbers(x,y)
end subroutine
subroutine get_array(x, z)
use iso_c_binding
real(8), intent(in) :: x
real(8), intent(out) :: z(100)
type(c_ptr) :: ret_c_ptr
real(8), pointer :: f_ptr(:)
! Interface to C function
interface
type(c_ptr) function c_get_array(a) bind(C, name="get_array")
import
real(c_double), value :: a
end function
end interface
! Call C function
ret_c_ptr = c_get_array(x)
call c_f_pointer(ret_c_ptr, f_ptr, [100])
z = f_ptr
end subroutine
subroutine pass_by_reference(z)
use iso_c_binding
integer, intent(out) :: z
! Interface to C function
interface
subroutine c_pass_by_reference(a) bind(C, name="pass_by_reference")
import
integer(c_int) :: a
end subroutine
end interface
! Call C function
call c_pass_by_reference(z)
end subroutine
end module
I am writing an iso_c_binding in Fortran to call a C-function with the below prototype
int zmat_run(
const size_t inputsize,
unsigned char *inputstr,
size_t *outputsize,
unsigned char **outputbuf,
const int zipid,
int *ret,
const int iscompress
);
My question is how do I declare unsigned char **outputbuf, a pointer that is used inside the c-function to allocate output buffer, in this interface?
Also, what data type I should be using in Fortran as the real parameter to pass to this outputbuf parameter? should it be allocatable? (if it is allocated inside the c-function)?
I currently drafted this module, but haven't tested it (I doubt it will work).
module zmatlib
use iso_c_binding, only: c_char, c_size_t, c_ptr, C_NULL_CHAR
interface
integer(c_int) function zmat_run(inputsize, inputbuf, outputsize, outputbuf, zipid, ret, level) bind(C, name="zmat_run")
use iso_c_binding
integer(c_size_t), value :: inputsize
integer(c_int), value :: zipid, level
integer(c_size_t), intent(out) :: outputsize
integer(c_int), intent(out) :: ret
character(kind=c_char), intent(in) :: inputbuf(*)
character pointer(c_ptr),intent(out) :: outputbuf
end function zmat_run
end interface
end module
Try type (C_PTR), intent (out). Then you will need to use Fortran function c_f_pointer to associate the C pointer with a Fortran pointer. Probably of type C_CHAR.
I want to combine C++ and Fortran together. My Fortran code will use a C++ function and C++ function changes variables of Fortran and sends them back. The C++ function is built with other C++ codes, e.g. the C++ function will use some sub-function in other .cpp file. I make the Fortran code with ifort and I added that C++ function as one object file, test.o in my Fortran makefile. I also put every needed C++ .o file(support test.o) in makefile. It shows the error
#6633, "The type of the actual argument differs from the type of the dummy argument".
Here is the code.
Fortran code
use, intrinsic :: ISO_C_BINDING, only: C_INT, C_DOUBLE
implicit double precision(a-h,o-z),integer(i-n)
Interface
integer (C_INT) function SolveBIE_(x, y, aa, m) BIND(C, NAME='SolveBIE_')
use, intrinsic :: ISO_C_BINDING
implicit none
type (C_PTR), value :: x
type (C_PTR), value :: y
type (C_PTR), value :: aa
integer (C_INT), value :: m
end function SolveBIE_
end Interface
integer (C_INT) :: m
real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: x
real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: y
real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: aa
ALLOCATE(x(0:MAXLEN,MAXINTERFACES))
ALLOCATE(y(0:MAXLEN,MAXINTERFACES))
ALLOCATE(aa(0:MAXLEN,MAXINTERFACES))
My Fortran code run
mm = SolveBIE_(x(1,1),y(1,1),aa(1,1),m)
Using the C++ code and where the error is from, on x, y, aa
I use x(1,1) instead of x, because if using x, then there is another error
#6634,"the shape matching rules of actual arguments and dummy arguments have been violated"`
I don't understand why it should be x(1,1). Why is this working, not x?
My C++ code
#ifdef __cplusplus
extern "C" {
#endif
int solveBIE_(double *ini_bdry_x, double *ini_bdry_y, double *ini_bdry_um, int *fM)
{
double(*bdry_node)[2] = new double[M1][2];
for (int k = 0; k < M; k++) {
bdry_node[k+1][0] = ini_bdry_x[k+1];
bdry_node[k+1][1] = ini_bdry_y[k+1];
bdry_theta[k+1] = Atan(ini_bdry_x[k+1], ini_bdry_y[k+1]);}
... some functions in other .cpp file
The way your interface is written, you have to construct a C_PTR to array x and pass that as the first argument:
use, intrinsic :: ISO_C_BINDING, only: C_INT, C_DOUBLE, C_PTR, C_LOC
! ...
type(C_PTR) PTRx
! ...
PTRx = C_LOC(x(LBOUND(x,1),LBOUND(x,2)))
! ...
mm = solveBIE_(PTRx, PTRy, PTRaa, m)
As shown above, you would have to fix the next two arguments as well. But you need to rewrite the interface for argument fM because as matters stand, Fortran will pass an integer by value whereas C++ is expecting a pointer. Given that, I would rewrite the interface completely, using the names given for the arguments in the C++ function and passing everything by reference. Names for dummy arguments are potentially visible in Fortran, so it's useful for them to be meaningful. In the following I assume that fM points to a scalar in the callee:
Interface
function SolveBIE_(ini_bdry_x, ini_bdry_y, ini_bdry_um, fM) &
BIND(C, NAME='SolveBIE_')
import
implicit none
integer(C_INT) SolveBIE_
real(C_DOUBLE) :: ini_bdry_x(*)
real(C_DOUBLE) :: ini_bdry_y(*)
real(C_DOUBLE) :: ini_bdry_um(*)
integer (C_INT) :: fM
end function SolveBIE_
end Interface
Then later on you can invoke it more or less normally as
mm = SolveBIE_(x,y,aa,m)
Note that x(1,1) was wrong because LBOUND(x,1) = 0, not 1!