Dear all,
I have the following C function:
void foo_c(char ***names, size_t *names_n,
int *ierr);
I want to call this function from Fortran.
So I created a module called foo_interface.f90 and put following code init.
INTERFACE
FUNCTION foo_c(names, names_n, ierr) RESULT( ans ) &
& BIND( C, NAME="foo_c")
USE ISO_C_BINDING, ONLY : C_PTR, C_INT, C_SIZE_T
TYPE( C_PTR ), INTENT( IN ) :: names
INTEGER( C_SIZE_T ), INTENT( OUT ) :: names_n
INTEGER( C_INT ), INTENT(OUT) :: ierr
TYPE( C_PTR ) :: ans
END FUNCTION foo_c
END INTERFACE
PUBLIC :: foo_c
I define following subroutine which calls foo_c as follows:
FUNCTION call_foo_c(names, names_n) RESULT( ans )
CHARACTER( LEN = 120 ), ALLOCATABLE, INTENT( OUT ) :: names( : )
INTEGER, INTENT( OUT ) :: names_n
INTEGER :: ans
! Internal variables
character(len=1,kind=C_char), pointer :: names_(:,:)
TYPE( C_PTR ) :: cstring, C_VOID
INTEGER( C_SIZE_T ) :: names_n_
INTEGER( I4B ) :: I
INTEGER( C_INT ) :: ierr
C_VOID = foo_c( cstring, names_n_, ierr )
names_n = names_n_
ALLOCATE( names( names_n ) )
DO i=1, names_n; names( i ) = ''; END DO
ans = INT( ierr, KIND=I4B)
!! CALL c_f_pointer( cstring, names_, [names_n, ??<-- what should be the shape?? ] )
!! How to copy data inside name(:)????
END FUNCTION model_list
I am able to get correct values of names_n
, but I am do not. know how to get a vector of strings? Please help me.
Regards
Vikas