11

I've been held up on this for about a week, now, and have searched forum after forum for a clear explanation of how to send a char* from C to FORTRAN. To make the matter more frustrating, sending a char* argument from FORTRAN to C was straight-forward...

Sending a char* argument from FORTRAN to C (this works fine):

// The C header declaration (using __cdecl in a def file):
extern "C" double GetLoggingValue(char* name);

And from FORTRAN:

! The FORTRAN interface:
INTERFACE
    REAL(8) FUNCTION GetLoggingValue [C, ALIAS: '_GetLoggingValue'] (name)
        USE ISO_C_BINDING       
        CHARACTER(LEN=1, KIND=C_CHAR), DIMENSION(*),    INTENT(IN) :: name                  
    END FUNCTION GetLoggingValue
END INTERFACE

! Calling the function:
GetLoggingValue(user_name)

When trying to use analogous logic to return a char* from C, I get problem after problem. One attempt that I felt should work is:

// The C declaration header (using __cdecl in a def file):
extern "C" const char* GetLastErrorMessage();

And the FORTRAN interface:

INTERFACE
    FUNCTION GetLastErrorMessage [C, ALIAS: '_GetLastErrorMessage'] ()
        USE ISO_C_BINDING   
        CHARACTER(LEN=1, KIND=C_CHAR), DIMENSION(255), :: GetLastErrorMessage
    END FUNCTION GetLastErrorMessage
END INTERFACE

(I can't literally use the DIMENSION(*), so I've gone oversize to 255.)

This should return a pointer to an array of 255 C-style characters - but if it does, I've been unable to convert this to a meaningful string. In practice, it returns a random set of characters, anywhere from Wingdings to the 'bell' character...

I've also attempted to return:

  • A pointer to CHARACTER(LEN=255, KIND=C_CHAR).
  • Literally CHARACTER(LEN=255, KIND=C_CHAR).
  • A INTEGER(C_SIZE_T), and tried to finesse that into a pointer to a string array.
  • A CHARACTER.
  • etc.

If anybody can give me an example of how to do this, I would be very grateful...

Best regards,

Mike

M. S. B.
  • 28,968
  • 2
  • 46
  • 73
Mike Sadler
  • 1,750
  • 1
  • 20
  • 37
  • What toolchains are you using? – Michael Burr Apr 02 '12 at 08:07
  • I'm using VC++ compiler, but compiling the interface in pure C. The FORTAN is Visual Fortran 2011, which I believe is FORTRAN 90. However, this is for a published API, so it must be callable from as many flavours as posible... – Mike Sadler Apr 02 '12 at 08:19

7 Answers7

14

Strings of dynamic length are always a bit tricky with the C interaction. A possible solution is to use pointers.

First a simple case, where you have to hand over a null-character terminated string to a C-Function. If you really pass the string only in, you have to ensure to finalize it with the c_null_char, thus this direction is pretty straight forward. Here are examples from a LuaFortran Interface:

subroutine flu_getfield(L, index, k)
  type(flu_State)  :: L
  integer          :: index
  character(len=*) :: k

  integer(kind=c_int) :: c_index
  character(len=len_trim(k)+1) :: c_k

  c_k = trim(k) // c_null_char
  c_index = index
  call lua_getfield(L%state, c_index, c_k)
end subroutine flu_getfield

And the interface of lua_getfield looks like:

subroutine lua_getfield(L, index, k) bind(c, name="lua_getfield")
  use, intrinsic :: iso_c_binding
  type(c_ptr), value :: L
  integer(kind=c_int), value :: index
  character(kind=c_char), dimension(*) :: k
end subroutine lua_getfield

And the C-Code interface is:

void lua_getfield (lua_State *L, int idx, const char *k)

Now the little more complex case, where we have to deal with a returned string from C with a dynamic length. The most portable solution I found so far is using pointers. Here is an example with a pointer, where the string is given by the C-Routine (also from the Aotus library mentioned above):

function flu_tolstring(L, index, len) result(string)
  type(flu_State) :: L
  integer :: index
  integer :: len
  character,pointer,dimension(:) :: string

  integer :: string_shape(1)
  integer(kind=c_int) :: c_index
  integer(kind=c_size_t) :: c_len
  type(c_ptr) :: c_string

  c_index = index
  c_string = lua_tolstring(L%state, c_index, c_len)
  len = int(c_len,kind=kind(len))
  string_shape(1) = len
  call c_f_pointer(c_string, string, string_shape)
end function flu_tolstring

where lua_tolstring has the following interface:

function lua_tolstring(L, index, len) bind(c, name="lua_tolstring")
  use, intrinsic :: iso_c_binding
  type(c_ptr), value :: L
  integer(kind=c_int), value :: index
  integer(kind=c_size_t) :: len
  type(c_ptr) :: lua_tolstring
end function lua_tolstring

Finally, here is an attempt to clarify how a c_ptr can be interpreted as a Fortran character string: Assume you got a c_ptr pointing to the string:

type(c_ptr) :: a_c_string

And the length of it is given by a len variable with the following type:

integer(kind=c_size_t) :: stringlen

You want to get this string in a pointer to a character string in Fortran:

character,pointer,dimension(:) :: string

So you do the mapping:

call c_f_pointer(a_c_string, string, [ stringlen ])
haraldkl
  • 3,809
  • 26
  • 44
  • Thanks, heraldkl! The example above is to interface to a void C function - would this approach work when the return type of the C function is a char*? My general operating paradigm is for my API functions to return the result, rather than to pass them via void subroutines, and this works fine when using all other datatypes EXCEPT chars :-( – Mike Sadler Apr 02 '12 at 09:37
  • I guess the approach above would also work with non-void functions. I do not see a reason, why this should be influenced by the return value. – haraldkl Apr 02 '12 at 10:10
  • I'm certainly happy to use pointers - indeed, that was my first approach. I'm afraid I'm having trouble following the snippets you've provided above - is it all necessary to convert a C pointer to a const char array to a FORTRAN string? To put it another way, if I have a TYPE(C_PTR) and a string length, what is the minimum I need to convert this to a FORTRAN string? Sorry to be obtuse... – Mike Sadler Apr 02 '12 at 10:51
  • tried to append some example for the transfer to my answer now ;) – haraldkl Apr 02 '12 at 14:21
  • IT WORKS! Thank you very, very much heraldkl - I was close to thinking that it was impossible. Thanks to all the guys who've helped and commented - it's kept me going. – Mike Sadler Apr 02 '12 at 14:30
  • I've added an 'answer' below, showing the final implementation. This should be a fairly generic way of interfacing to a char* using heraldkl's solution. I hope that I'm not breaking any etiquette by answering my own question - even if it is to pay homage to be better's solution... – Mike Sadler Apr 03 '12 at 08:22
5

This thread is a little old, but since I had a similar problem (and probably others will), I post a answer anyway.

The codes posted above will cause a segmentation fault if, for some reason, the C string is null. In addition, there is no need to return a 255-chars string (which will probably need to be trimmed before used), as Fortran 2003/2008 supports functions returning allocatable entities. Using all the information posted above, I ended up with the following function, which gets a C string (pointer), and returns the corresponding Fortran string; If the C string is null, it returns "NULL", similarly to C's "(null)" printed in similar cases:

function C_to_F_string(c_string_pointer) result(f_string)
use, intrinsic :: iso_c_binding, only: c_ptr,c_f_pointer,c_char,c_null_char
type(c_ptr), intent(in) :: c_string_pointer
character(len=:), allocatable :: f_string
character(kind=c_char), dimension(:), pointer :: char_array_pointer => null()
character(len=255) :: aux_string
integer :: i,length
call c_f_pointer(c_string_pointer,char_array_pointer,[255])
if (.not.associated(char_array_pointer)) then
  allocate(character(len=4)::f_string); f_string="NULL"; return
end if
aux_string=" "
do i=1,255
  if (char_array_pointer(i)==c_null_char) then
    length=i-1; exit
  end if
  aux_string(i:i)=char_array_pointer(i)
end do
allocate(character(len=length)::f_string)
f_string=aux_string(1:length)
end function C_to_F_string
Pap
  • 448
  • 1
  • 10
  • 15
5

My thanks to heraldkl for giving me the solution to this very frustrating problem. I'm posting what I've eventually implemented, which roles the pointer conversion into the interface, meaning the final application can call the C function without having to know about the pointer conversion:

The C function:

// The C declaration header (using __cdecl in a def file):
extern "C" const char* GetLastErrorMessage();

The FORTRAN interface module:

MODULE mINTERFACES

USE ISO_C_BINDING

INTERFACE
    FUNCTION GetLastErrorMessagePtr [C, ALIAS: '_GetLastErrorMessage'] ()
        USE ISO_C_BINDING   
    TYPE(C_PTR) :: GetLastErrorMessagePtr                   
    END FUNCTION GetLastErrorMessagePtr
END INTERFACE

CONTAINS    ! this must be after all INTERFACE definitions

FUNCTION GetLastErrorMessage()
    USE ISO_C_BINDING   
    CHARACTER*255 :: GetLastErrorMessage
    CHARACTER, POINTER, DIMENSION(:) :: last_message_array
    CHARACTER*255 last_message
    INTEGER message_length

    CALL C_F_POINTER(GetLastErrorMessagePtr(), last_message_array, [ 255 ])

    DO 10 i=1, 255
        last_message(i:i+1) = last_message_array(i)
10  CONTINUE

    message_length = LEN_TRIM(last_message(1:INDEX(last_message, CHAR(0))))

    GetLastErrorMessage = last_message(1:message_length-1)

END FUNCTION GetLastErrorMessage

And to call this function from a FORTRAN program:

USE MINTERFACES

PRINT *, "--> GetLastErrorMessage:      '", TRIM(GetLastErrorMessage()), "'"

My thanks again to heraldkl for providing this solution - I wouldn't have had a clue how do do this without his input.

Community
  • 1
  • 1
Mike Sadler
  • 1,750
  • 1
  • 20
  • 37
2

I have also struggled with calling a C routine that returns a string and the answers above has been very useful but as I know almost nothing of C and the answers are slightly confusing I just wanted to contribute my solution which uses a C pointer, I did not manage to make use any of the other proposals above. The C program I call opens a separate window to browse for a file name.

program test
  use iso_c_binding
  implicit none
! A C function that returns a string need a pointer to the array of single char 
  type (c_ptr) :: C_String_ptr
! This is the Fortran equivalent to a string of single char
  character (len=1, kind=c_char), dimension(:), pointer :: filchar=>null()
! Interface to a C routine which opens a window to browse for a file to open
  interface
    function tinyopen(typ) bind(c, name="tinyopen")
       use iso_c_binding
       implicit none
       integer(c_int), value :: typ
       type (C_Ptr) :: tinyopen
    end function tinyopen
  end interface
  character (len=256) :: filename
  integer typ,jj
  typ=1
C_String_ptr = tinyopen(typ)
! convert C pointer to Fortran pointer
  call c_f_pointer(C_String_ptr,filchar,[256])
  filename=' '
  if(.not.associated(filchar)) then
! if no characters give error message
    write(*,*)'No file name'
  else
! convert the array of single characters to a Fortran character
    jj=1
    do while(filchar(jj).ne.c_null_char)
      filename(jj:jj)=filchar(jj)
      jj=jj+1
    enddo
  endif
  write(*,*)'Text is: ',trim(filename)
end program test

Hopefully this example will make it easier for the next one with the same problem.

Bo Sundman
  • 424
  • 3
  • 13
2

I always struggle with these interoperability features. I think that your interface should declare

CHARACTER(KIND=C_CHAR),DIMENSION(*) :: getlasterrormessage

and that, when you call the function, you pass a corresponding Fortran character variable with a length equal to or greater than the length of the array of C characters you expect to return.

Since you seem to have Intel Fortran, look through the code samples provided, they give a complete example for this.

I guess you know that what you have posted is not syntactically correct Fortran ?

High Performance Mark
  • 77,191
  • 7
  • 105
  • 161
  • You mean the comma before the ::? Sorry - a cut and paste error! I'll give the above a go... – Mike Sadler Apr 02 '12 at 09:06
  • I've just tried it, but I get the same compilation error as I had when I tried something similar: "Error 1 error #6688: The array-spec for a function name with no POINTER attribute must be an explicit shape array (R505.9)." This is why I'd tried basically the same, but with 255 instead of * - but with no success :-( – Mike Sadler Apr 02 '12 at 09:09
  • I've tried using "CHARACTER(KIND=C_CHAR),DIMENSION(255) :: GetLastErrorMessage" instead, and reading into a character array of the same spec, but this apparently returns an array of 255 random characters... – Mike Sadler Apr 02 '12 at 09:13
  • Hmmm, suggest you check out the Intel samples. I'll continue head-scratching, but ... – High Performance Mark Apr 02 '12 at 09:17
  • Thanks, Mark - I've had a look through the Intel directories, but I can only find an interface schema. I might be missing the examples in my installation... – Mike Sadler Apr 02 '12 at 09:32
  • I think he means that the fortran function signature in the interface block is invalid, specifically the square bracket notation. This is likely a compiler specific extension. The line in question should read: `FUNCTION GetLastErrorMessagePtr () bind(c,name='GetLastErrorMessagePtr')` I think the underscore isn't necessary since `bind(c)` should take care of name mangling unless something odd is happening, like interfacing with C++ or using a different compiler for your C code. In general `function func_name [stuff here] ()` is not a valid Fortran function declaration. – zbeekman Jul 16 '13 at 02:38
1

In Fortran the item needs to be declared as "character (kind=c_char,len=1), dimension (255)" rather than len=255. This will create an array of characters of length one, which is what you need on the C-side. What can be confusing is that there is a exception that allows Fortran to match strings against one-dimensional arrays.

You mean that you want to call a Fortran procedure from C? See this example: Calling a FORTRAN subroutine from C.

EDIT: Both ifort and gfortran say that arrays are not allowed as function returns in this context. Which makes returning strings as function arguments from C to Fortran harder than using a string as an argument (example in link above) ... you have to use pointer and then the c_f_pointer Fortran intrinsic to convert from the C-string to a Fortran string, as explained by haraldkl. Here is another code example:

program test_c_func

use iso_c_binding
implicit none

type (C_PTR) :: C_String_ptr
character (len=1, kind=c_char), dimension (:), pointer :: ErrChars => null ()
character (len=255) :: ErrString
integer :: i

INTERFACE
    FUNCTION GetLastErrorMessage ()  bind (C, name="GetLastErrorMessage" )
        USE ISO_C_BINDING
        type (C_PTR) :: GetLastErrorMessage
    END FUNCTION GetLastErrorMessage
END INTERFACE

C_String_ptr = GetLastErrorMessage ()
call c_f_pointer ( C_String_ptr, ErrChars, [255] )
ErrString = " "
xfer_string: do i=1, 255
   if ( ErrChars (i) == c_null_char) exit xfer_string
   ErrString (i:i) = ErrChars (i)
end do xfer_string

write (*, '( "Fortran: <", A, ">" )' )  trim (ErrString)

end program test_c_func
Community
  • 1
  • 1
M. S. B.
  • 28,968
  • 2
  • 46
  • 73
  • Hello M.S.B. - I have tried character (kind=c_char, len=1), dimension (255), which seems to return something, but it appears that the first element is a NULL char - which translates to being an empty string. As it returns the correct string when called directly from C, I have been assuming that the fault lies in the FORTRAN interface. Calling the FORTRAN from C doesn't appear to be so difficult - or at least, I can transfer strings from FORTRAN to C easily enough. – Mike Sadler Apr 02 '12 at 13:44
0

If you know the length of the string, then Pap's answer above can be greatly simplified:

function stringc2f(n, cstr) result(fstr)
integer, intent(in) :: n
type(c_ptr), intent(in) :: cstr
character(:), allocatable :: fstr
character(n, kind=c_char), pointer :: fptr
call c_f_pointer(cstr, fptr)
fstr = fptr
end function

The above function accepts a C pointer with the string and the length of the string, and returns a copy as a Fortran string.

Ondřej Čertík
  • 780
  • 8
  • 18
  • I'm not sure this is modern Fortran, while my answer isn't; in fact both codes are Fortran 2003. Anyway, your code is simpler BUT requires to pass the length of the string (`n`), as an argument. Of course, knowing the length of the string in advance makes the code much smaller, but also makes the function less useful. In most cases, you simply don't know how long the C string is. – Pap Jun 15 '17 at 11:18
  • @Pap, you are right. I have clarified my answer to reflect this. Indeed, both are F2003. I used the automatic allocation of the LHS, but that's also F2003. For my application, I have access to both C and Fortran codes, and so it's not a problem to pass the length of the C string into the interface, which greatly simplifies things. – Ondřej Čertík Jun 16 '17 at 14:34