Calling C code with in-memory data from Fortran - c++

I have a complicated C++ object that I'd like to use in my Fortran code.
In general , there is no problem in calling C++ code from Fortran (just need to provide a suitable interface with C linkage for instance).
However my problem here is that I want my Fortran calls to C++ to operate on what I would call a persistent object: a C++ object created by the first init function, and operated on by other C++ functions.
To be more specific, suppose I have the following C++ code
struct A {
public:
void do() { // do something on complicated stuff
private:
... // complicated stuff
};
extern "C" {
void* init_A() {
A* a = new A();
return reinterpret_cast<void*>(a);
}
void doSth(void* ptr_to_A) {
A* a = reinterpret_cast<A*>(ptr_to_A);
a.do();
}
void teardown_A(void* ptr_to_A) {
A* a = reinterpret_cast<A*>(ptr_to_A);
delete a;
}
}
And the following fortran code (suppose it is main() ):
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
INTERFACE
TYPE(C_PTR) FUNCTION init_A() BIND(C, NAME='init_A')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
END FUNCTION init_A
SUBROUTINE doSth(ptr_to_A) BIND(C, NAME='doSth')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
TYPE(C_PTR), INTENT(IN), VALUE :: ptr_to_A
END SUBROUTINE doSth
SUBROUTINE teardown_A(ptr_to_A) BIND(C, NAME='teardown_A')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
TYPE(C_PTR), INTENT(IN), VALUE :: ptr_to_A
END SUBROUTINE teardown_A
END INTERFACE
Now in my real code, this compiles, links, and sometimes works, but sometimes not:
it seems like the memory allocated in init_A() is not garanteed to be left unchanged by the Fortran code)
I wasn't able to find anything about that on the Internet:
Do you know if there is any standard mechanism to ensure that the memory allocated by init_A_() is left unchanged and still allocated by the fortran code ?
Do you know of any other mechanism that would suit my problem ?
Also, can someone explain me why the memory is not managed correctly ?
Until now, I thought that
Fortran would ask the OS for memory, C++ too,
Memory segments given by the OS to both Fortan and C++ were unrelated and garanteed to be non-overlapping,
If new memory was asked, the OS would not let Fortran use C++ memory until C++ freed it
The C++ memory is freed either by a call to teardown_A() or when the program (i.e. Fortran main) terminates
Edit : I updated my code with the answer of IanH, but this is still not working (segfaults, portions of memory are deallocated while calling doSth() from Fortran
The original code I posted is the following (for comments refering to it)
struct A {
public:
void do() { // do something on complicated stuff
private:
... // complicated stuff
};
extern "C" {
void init_A_(long* ptr_to_A) { // ptr_to_A is an output parameter
A* a = new A();
*ptr_to_A = reinterpret_cast<long>(a);
}
void doSth_(long* ptr_to_A) {
A* a = reinterpret_cast<A*>(*ptr_to_A);
a.do();
}
void teardown_A_(long* ptr_to_A) {
A* a = reinterpret_cast<A*>(*ptr_to_A);
delete a;
}
}
And the Fortran code:
integer :: ptr_to_A
call init_A(ptr_to_A)
do i=1,10000
call doSth(ptr_to_A)
enddo
call teardown_A(ptr_to_A)

Fortran 2003 introduced C interoperability into the Fortran language. This language feature makes it much easier to write Fortran and C (and hence C++) source that can work together in a portable and robust way. Unless you are prevented from using this level of the language for other reasons, you should very much use this feature.
You have an issue with pointer indirection - whether the pointer to the C++ object is being stored in a long or a pointer to long (the operand to the casts in doSth_ and teardown_A_ should have a * before them). It depends on the C++ and Fortran compilers that you are using, but it is possible that you have a size mismatch between a C long, a C pointer and a Fortran default kind integer.
A modified example showing the approach using Fortran 2003's C interoperability feature below.
// C++
struct A {
public:
void do_something()
{
// ...
}
private:
// ...
};
// Note no need for trailing underscore.
extern "C" {
// Note pointer to pointer to void.
void init_A(void** ptr_ptr_to_A) {
A* a = new A;
*ptr_ptr_to_A = reinterpret_cast<void*>(a);
}
void doSth(void* ptr_to_A) {
A* a = reinterpret_cast<A*>(ptr_to_A);
a->do_something();
}
void teardown_A(void* ptr_to_A) {
A* a = reinterpret_cast<A*>(ptr_to_A);
delete a;
}
}
! Fortran 2003
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
INTERFACE
SUBROUTINE init_A(ptr_to_A) BIND(C, NAME='init_A')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
! This argument is a pointer passed by reference.
TYPE(C_PTR), INTENT(OUT) :: ptr_to_A
END SUBROUTINE init_A
SUBROUTINE doSth(ptr_to_A) BIND(C, NAME='doSth')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
! This argument is a pointer passed by value.
TYPE(C_PTR), INTENT(IN), VALUE :: ptr_to_A
END SUBROUTINE doSth
SUBROUTINE teardown_A(ptr_to_A) BIND(C, NAME='teardown_A')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
IMPLICIT NONE
! This argument is a pointer passed by value.
TYPE(C_PTR), INTENT(IN), VALUE :: ptr_to_A
END SUBROUTINE teardown_A
END INTERFACE
TYPE(C_PTR) :: ptr_to_A
INTEGER :: i
!****
CALL init_A(ptr_to_A)
DO i = 1, 100
CALL doSth(ptr_to_A)
END DO
CALL teardown_A(ptr_to_A)
END

Related

Problems with passing data between C++ and F90

Update: I changed psubstuff into a c_ptr as recommended and used a c_f_pointer to access bstuff. This was successful. However I still need a good t_stuff structure with the second member as a t_bstuff (for further code in the real world), so I created a copy of the t_stuff (the bind(c) version I called t_stuff_c), and am trying to copy the contents of the t_stuff_c structure into t_stuff. But I am getting a compilation error:
error #6285: There is no matching specific subroutine for this generic subroutine call. [C_F_POINTER]
I have a situation where a C++ main program is calling functions in a Fortran DLL. This comes from a very large project, so I have trimmed it down into a simple example which reproduces the problem I am having, which is:
The main C++ program creates a variable "stuff" of type "tstuff". "tstuff" contains just one element "substuff" which is of type "void*" (it has to be this way as in practice substuff is extremely large and complex on the F90 side and I can't and indeed don't need to reproduce it on the C++ side)
It then calls crfl() in the Fortran code which creates "substuff" on the Fortran side.
Then it calls the function stfl in the Fortran code to send the character "TEST" into the member substuff%clb%corf on the Fortran side. I step through the debugger in the Fortran code and all is good up to this point and "TEST" does indeed appear in the variable on the Fortran side.
Now it goes strange. The C++ code then calls the Fortran routine test2 passing the variable stuff. When I step into the F90 code, stuff%substuff%clb%corf contains garbage. The pointer to stuff is correct in the Fortran code as the text "ACF-C" is in the name variable. But substuff is garbage. It is important that the variable stuff%substuff is correct at this point as this variable is used further in the real code.
C Code:
#include <iostream>
#include <cstddef>
#include <vector>
using namespace std;
struct t_stuff {
char name[256];
void *substuff;
};
//Fortran subroutine definitions
extern "C" {
void test2(t_stuff *stuff);
}
extern "C"
{
void * crfl();
int stfl(void * cstuff, char * name);
}
int main()
{
int ierr;
t_stuff *stuff;
stuff = new t_stuff;
strcpy_s((*stuff).name, sizeof((*stuff).name), "ACF-C");
(*stuff).substuff = crfl();
ierr = stfl((*stuff).substuff, "TEST");
test2(stuff);
}
Fortran code:
module ftncode_mod
use, intrinsic :: iso_c_binding
implicit none
type, public :: t_clb
character(8) :: corf
end type
type, public :: t_bstuff
type (t_clb) :: clb
end type t_bstuff
type, public, bind(C) :: t_stuff_c
character(1) :: name(256)
type (c_ptr) :: psubstuff
end type t_stuff_c
type, public :: t_stuff
character :: name(256) = ' '
type (t_bstuff) :: psubstuff
end type t_stuff
contains
subroutine c2fstr(cptr,fstr)
type(c_ptr), value, intent(in ) :: cptr
character(*), intent(out) :: fstr
character(256), pointer :: lfstr
integer :: id
call c_f_pointer(cptr,lfstr)
id = index(lfstr,c_null_char)-1
if(id.le.0) id=len(lfstr)
fstr = lfstr(1:id)
end subroutine
function crfl() result(cp) bind(C)
!DEC$ ATTRIBUTES DLLEXPORT :: crfl
type(c_ptr ) :: cp
type(t_bstuff), pointer :: fp
allocate(fp)
cp = c_loc(fp)
end function
function stfl(cstuff,cne) result(ierr) bind(C)
!DEC$ Attributes dllexport :: stfl
type(c_ptr), value, intent(in) :: cstuff
type(c_ptr), value, intent(in) :: cne
integer :: ierr
type(t_bstuff) , pointer :: fstuff
character(24) :: cwk
ierr = 0
call c_f_pointer(cstuff,fstuff)
call c2fstr(cne,cwk)
fstuff%clb%corf = trim(cwk)
end function
subroutine test2(stuff) bind(C)
!DEC$ATTRIBUTES DLLEXPORT :: test2
use iso_c_binding
type(t_stuff_c), target, intent(in) :: stuff
type(t_stuff) :: fstuff
type(t_bstuff), pointer :: bstuff
integer :: i
call c_f_pointer(stuff%psubstuff,bstuff)
print *, "stuff%substuff%clb%corf: ", bstuff%clb%corf ! correct
! now need to populate the derived Fortran structure, fstuff
do i = 1, 256
if(stuff%name(i) == c_null_char) exit
fstuff%name(i:i) = stuff%name(i)
enddo
! and the pointer
call c_f_pointer(stuff,fstuff)
print *, "fstuff%substuff%clb%corf: ", fstuff%psubstuff%clb%corf
end subroutine test2
end module

Is it possible to call a Fortran interface from C++

I have the following code that does not compile. Is it possible to call the Fortran interface as overloaded functions in C++, as I try below?
This is the Fortran code:
module functions
use, intrinsic :: iso_c_binding, only : c_double, c_int
implicit none
interface increment bind(c, name="increment")
module procedure increment_int, increment_double
end interface
contains
subroutine increment_int(a, b)
integer(c_int), intent(inout) :: a
integer(c_int), value :: b
a = a + b
end subroutine
subroutine increment_double(a, b)
real(c_double), intent(inout) :: a
real(c_double), value :: b
a = a + b
end subroutine
end module functions
And this is the C++ code:
#include <iostream>
namespace
{
extern "C" void increment(int&, int);
extern "C" void increment(double&, double);
}
int main()
{
int a = 6;
const int b = 2;
double c = 6.;
const int d = 2.;
increment(a, b);
increment(c, d);
std::cout << "a = " << a << std::endl;
std::cout << "c = " << c << std::endl;
return 0;
}
No, it cannot be avoided. But you can instantiate a template to call the two. Or just make a C++ generic wrapper to those two extern C functions. You definitely cannot make Fortran to export the interface. Interface is just a description how to call the two subroutines under some name internally in Fortran.
This question importing interface module procedure from fortran into C is very similar. I even originally closed yours as a duplicate, but then I changed my mind because the attempted solution is slightly different.
But the principle is the same. Fortran generics and C++ generics are not compatible. And you have C between them which has no generics of similar type.
Note: As #RichardCritten suggest you also should not pass by reference in an extern C function. The compiler probably compiles it and implements as passing a pointer by value, but it is not guaranteed. Just pass a pointer. See C++ by-reference argument and C linkage for more.

Fortran/C interoperability program crashes at C_LOC

I had asked a related question before.
Passing a structured data type from Fortran to C++
But it was a duplicate of the following question:
Fortran derived types containing pointers to be accessible from C
I created a simple example, but my program crashes when calling the C_LOC
Here is the complete example (short, self-contained, executable)
File: mydata.f90
module mydata
type mytype
integer :: loaded
integer :: status
end type mytype
CONTAINS
FUNCTION GetHandle() RESULT(handle) BIND(C, NAME = 'GetHandle')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_LOC
TYPE(C_PTR) :: handle
TYPE(mytype), POINTER :: p
ALLOCATE(p)
p % loaded = 1122334455
p % status = 1234567890
write(*, *) 'GetHandle:p_addr = ', loc(p)
write(*, *) 'GetHandle:p%loaded = ', p % loaded
write(*, *) 'GetHandle:p%status = ', p % status
handle = C_LOC(p)
END FUNCTION GetHandle
SUBROUTINE ReleaseHandle(handle) BIND(C, NAME = 'ReleaseHandle')
USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_F_POINTER
TYPE(C_PTR), INTENT(IN), VALUE :: handle
TYPE(mytype), POINTER :: p
CALL C_F_POINTER(handle, p)
DEALLOCATE(p)
END SUBROUTINE ReleaseHandle
end module mydata
File: dostuff.f90
subroutine STUFF(handle, ier) BIND(C, NAME = 'STUFF')
use mydata
USE, INTRINSIC :: ISO_C_BINDING
implicit none
TYPE(C_PTR), INTENT(IN), VALUE :: handle
TYPE(mytype), POINTER :: p
INTEGER :: ier
CALL C_F_POINTER(handle, p)
write(*, *) 'FITC:p_addr = ', loc(p)
write(*, *) 'FITC:s%loaded = ', p % loaded
write(*, *) 'FITC:s%status = ', p % status
end
File: main.cpp
#include <cstdio>
#include <cstdlib>
using namespace std;
#ifdef __cplusplus
extern "C" {
#endif
void* GetHandle();
void ReleaseHandle(void* handle);
void STUFF(void *handle, int *ierr);
#ifdef __cplusplus
}
#endif
int main(int argc, const char* const argv[]) {
void *handle;
int ierr = 0;
handle = GetHandle();
STUFF(handle, &ierr);
ReleaseHandle(handle);
return 0;
}
I am using intel C++/fortran compiler on Linux 64 bit.
Any ideas how to fix the error?
Edit: The exact error message is as follows (gdb output).
Program received signal SIGSEGV, Segmentation fault.
0x00000000004031ff in MYDATA::gethandle (handle=<error reading variable: Cannot access memory at address 0x1>) at mydata.f90:20
20 handle = C_LOC(p)
(gdb) bt
#0 0x00000000004031ff in MYDATA::gethandle (handle=<error reading variable: Cannot access memory at address 0x1>) at mydata.f90:20
#1 0x0000000000402efa in main (argc=1, argv=0x7fffffffdf88) at main.cpp:19
Without gdb, there is simply c crash with Memory fault.

Fortran-C function pointer causing seg fault from C code in certain circumstances

I am modifying fgsl so I can pass a function pointer instead of the name of a function. To do this I use a Fortran bind(c) function, call c_funloc, call the C function and assign that to a derived type(c_ptr). However, the C code gives me segfaults depending on how I implement the code.
C Code:
#include <stdio.h>
#include <stdlib.h>
struct function_struct
{
double (* function) (double x);
};
typedef struct function_struct gsl_function;
gsl_function *function_cinit(double (*func)(double x)) {
gsl_function *result;
if (func) {
printf("Passed Function Not Null\n");
}
printf("The size of gsl_function is %zu\n", sizeof(gsl_function));
result = (gsl_function *) malloc(sizeof(gsl_function));
result->function = func;
printf("Res: %f\n", (*func)(2.0));
if (result) {
printf("Result Not Null\n");
}
return result;
}
Now my main program/module:
module integral
use, intrinsic :: iso_c_binding
implicit none
!Interface to call C function
interface
function function_cinit(func) bind(c)
import
type(c_funptr), value :: func
type(c_ptr) :: function_cinit
end function function_cinit
end interface
!Proc pointer interface for arbitrary math function f(x) which is passed to the C function so it can be used in a library that requires
! a pointer to a function
abstract interface
function rhox(r) bind(c)
use, intrinsic :: iso_c_binding
real(c_double), value :: r
real(c_double) :: rhox
end function rhox
end interface
contains
! Arbitary function f(x) = x
function f(x) bind(c)
use, intrinsic :: iso_c_binding
real(c_double) :: f
real(c_double), value :: x
f = x
end function f
!Function passed by name
function func_init(func)
interface
function func(x) bind(c)
use, intrinsic :: iso_c_binding
real(c_double), value :: x
real(c_double) :: func
end function func
end interface
type(c_ptr) :: func_init
type(c_funptr) :: fp
fp = c_funloc(func)
func_init = function_cinit(fp)
end function func_init
!Function passed with procedure pointer
function fp_init(fun)
procedure(rhox), pointer :: fun
type(c_ptr) :: fp_init
type(c_funptr) :: fp
fp = c_funloc(fun)
call c_f_procpointer(fp, fun)
fp_init = function_cinit(fp)
end function fp_init
!C_funptr passed directly
function cfun_ptr_init(fun)
type(c_funptr) :: fun
type(c_ptr) cfun_ptr_init
cfun_ptr_init = function_cinit(fun)
end function cfun_ptr_init
end module integral
program bsp
use integral
use, intrinsic :: iso_c_binding
implicit none
procedure(rhox), pointer :: fptr
type(c_funptr) :: cptr
type(c_ptr) :: c_result
fptr => f
cptr = c_funloc(fptr)
call c_f_procpointer(cptr, fptr)
!This works, calling the cptr after calling c_f_procpointer on c_funptr obtained by using c_funloc
print *, "Evaluate C Function: ", fptr(2.0_c_double)
print *, ""
!This Works f(2.0) = 2.0, valid pointer
c_result = func_init(f)
print *,"Passing Function Directly Successful"
print *, " "
!This works, calling C function directly from main program passing it the c_funloc of the procedure8
c_result = function_cinit(cptr)
print *,"Calling C Function Directly Successful"
print *, " "
c_result = cfun_ptr_init(cptr)
print *,"Calling C function by Passing c_funptr Successful"
print *, " "
!Segmentation Fault 11, calling C function indirectly from function which I pass the Fortran Proc pointer
c_result = fp_init(fptr)
end program bsp
Found the answer! Turns out I didn't have to change a thing to allow the code to accept procedure pointers.
!Function passed with procedure pointer
function fp_init(fun)
!Changed from:
!procedure(rhox), pointer :: fun
procedure(rhox):: fun
type(c_ptr) :: fp_init
type(c_funptr) :: fp
fp = c_funloc(fun)
call c_f_procpointer(fp, fun)
fp_init = function_cinit(fp)
end function fp_init
I removed the "pointer" attribute from the dummy argument and now it works. I'm not sure why though.

Why is this attempt to pass a pointer from C++ to Fortran not working?

I need to pass a dynamic array from c++ to Fortran. I did a lot of research to put together an example that I thought should work, but it doesn't. The program should create an array in the c++ program, pass the pointer of that array to the Fortran routine, convert the C pointer to a Fortran pointer, and then print the array on the Fortran side.
My c++ main program:
using namespace std;
extern "C" {
void cinterface(int*,int*);
}
int main()
{
int carray[]={0,1,2,3,4};
int carray_siz=5;
cinterface(&carray_siz,carray);
return 0;
}
My Fortran routine:
module fortmod
use ISO_C_BINDING
implicit none
contains
subroutine cinterface(carray_siz,carray_ptr) bind(C)
implicit none
integer(c_int), intent(in) :: carray_siz
type(c_ptr), intent(in) :: carray_ptr
integer(c_int), pointer :: pfarray(:) => NULL()
call C_F_POINTER(carray_ptr,pfarray,[carray_siz])
print *, pfarray
end subroutine cinterface
end module fortmod
I build this as:
gfortran -c fortmod.f90
g++ main.cpp fortmod.o -lgfortran
But when I run it, instead of printing the array values, it says:
Segmentation fault (core dumped)
I'm new to the idea of pointers, so I'm thinking I'm not understanding how they work correctly. Can you please point out why I'm getting this memory error when I run this?
Surely you want to pass the array size as int, not the address of the size:
extern "C" {
void cinterface(int,int*);
}
cinterface(carray_siz,carray);
From the gfortran manual:
If a pointer is a dummy-argument of an interoperable procedure, it usually has to be
declared using the VALUE attribute. void* matches TYPE(C_PTR), VALUE, while TYPE(C_PTR) alone matches void**.
My Fortran routine was looking for the address of the pointer, not the address to which the pointer is pointing. So if I modify the c++ side to this:
using namespace std;
extern "C" {
void cinterface(int*,int**);
}
int main()
{
int carray[]={0,1,2,3,4};
int carray_siz=5;
cinterface(&carray_siz,&carray);
return 0;
}
re-build and re-run, I now get:
0 1 2 3 4
as expected.