Reputation: 177
I think title says what I need. I know we can use "asd" function to do this, but for some reasons I need to do the allocation in Fortran (i.e. in subroutine "asd_"). Here is the C code:
#include <stdio.h>
void asd(float **c) {
*c = (float *) malloc (2*sizeof(float));
**c =123;
*(*c+1)=1234;
}
void asd_(float **c);
main () {
float *c;
asd_(&c);
// asd(&c); would do the job perfectly
printf("%f %f \n",c[0],c[1]);
return 0;
}
And here is the Fortran code:
subroutine asd(c)
implicit none
real, pointer, allocatable ::c(:)
print *, associated(c)
if(.not. associated(c)) allocate(c(2))
end subroutine
This randomly gives segmentation fault. Any help would be appreciated.
Upvotes: 5
Views: 1764
Reputation: 3812
If you need a thread safe solution and/or the possibility to deallocate the space from C again, the example below would do the job:
#include <stdio.h>
void test_mem_alloc(float ** array, void **wrapper);
void free_wrapper(void **wrapper);
int main()
{
float *array;
void *wrapper;
/* Allocates space in Fortran. */
test_mem_alloc(&array, &wrapper);
printf( "Values are: %f %f\n", array [0], array [1]);
/* Deallocates space allocated in Fortran */
free_wrapper(&wrapper);
return 0;
}
On the Fortran side, you have a general wrapper type CWrapper
, which can carry any type of derived type. Latter contains the data you would like to pass around. The CWrapper
type accept arbitrary payload, and you would always invoke the free_wrapper()
routine from C to release the memory.
module memalloc
use, intrinsic :: iso_c_binding
implicit none
type :: CWrapper
class(*), allocatable :: data
end type CWrapper
type :: CfloatArray
real(c_float), allocatable :: array(:)
end type CfloatArray
contains
subroutine test_mem_alloc(c_array_ptr, wrapper_ptr)&
& bind(C, name="test_mem_alloc")
type (c_ptr), intent (out) :: c_array_ptr
type(c_ptr), intent(out) :: wrapper_ptr
type(CWrapper), pointer :: wrapper
allocate(wrapper)
allocate(CfloatArray :: wrapper%data)
select type (data => wrapper%data)
type is (CfloatArray)
allocate(data%array(2))
data%array(:) = [2.5_c_float, 4.4_c_float]
c_array_ptr = c_loc(data%array)
end select
wrapper_ptr = c_loc(wrapper)
end subroutine test_mem_alloc
subroutine free_cwrapper(wrapper_ptr) bind(C, name='free_wrapper')
type(c_ptr), intent(inout) :: wrapper_ptr
type(CWrapper), pointer :: wrapper
call c_f_pointer(wrapper_ptr, wrapper)
deallocate(wrapper)
end subroutine free_cwrapper
end module memalloc
Upvotes: 2
Reputation: 177
Here is also another solution, if you want to use Fortran intrinsic types. This was my case, since I needed to call routines from an external library, using the pre-specified data types. This is basically done with a wrapper Fortran subroutine. Here is the C code:
void mywrap_(void **);
void myprint_(void *);
main () {
void *d;
mywrap_(&d);
myprint_(d);
return 0;
}
And here is the wrapper:
subroutine mywrap(b)
implicit none
include "h.h"
type(st), target, save :: a
integer, pointer :: b
interface
subroutine alloc(a)
include "h.h"
type(st) a
end subroutine alloc
end interface
call alloc(a)
b => a%i
end
And the Fortran codes:
subroutine alloc(a)
implicit none
include "h.h"
type(st) a
a%i = 2
a%r = 1.5
if (allocated(a%s)) deallocate(a%s)
allocate(a%s(2))
a%s(1) = 1.23
a%s(2) = 1234
end
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine myprint(a)
implicit none
include "h.h"
type(st) a
print *,"INT: ", a%i
print *,"REAL: ", a%r
print *,"ALLOC: ", a%s
end
And the header file "h.h":
type st
sequence
integer i
real r
real, allocatable :: s(:)
end type
Note, this way all the objects are opaque in the C.
Upvotes: 1
Reputation: 29401
The Fortran 2003 ISO C Binding provides a portable way to do this. It is implemented in many compilers. Here is example code.
#include <stdio.h>
void test_mem_alloc ( float ** array );
int main ( void ) {
float * array;
test_mem_alloc (&array);
printf ( "Values are: %f %f\n", array [0], array [1] );
return 0;
}
and
subroutine test_mem_alloc ( c_array_ptr ) bind (C, name="test_mem_alloc")
use, intrinsic :: iso_c_binding
implicit none
type (c_ptr), intent (out) :: c_array_ptr
real (c_float), allocatable, dimension (:), target, save :: FortArray
allocate (FortArray (1:2) )
FortArray = [ 2.5_c_float, 4.4_c_float ]
c_array_ptr = c_loc (FortArray)
end subroutine test_mem_alloc
Upvotes: 10