Experiment: dealing with a pointer to a string from C

I was experimenting with an interface to a C library and realised that I would need to deal with pointers to C strings and if possible in a way that is transparent on the Fortran side. So: turn the type(c_ptr) into a string that behaves as if it is an ordinary Fortran string (because otherwise dealing with them is awkward). There are a number of possibilities for that, one being creating a copy of the contents in an ordinary Fortran variable. But what if I want to avoid the copy?

Well, here is the C code as an example, the function returns a pointer to a string ending in a NUL character:

/* getstring.c --
   Trivial function to return a static string   
*/

#include <string.h>

void getstring_c( char **string, int *length ) {

     *string = "Hello" ;
     *length = strlen(*string) ;
}

(quite trivial, but the interface is typical for what I was dealing with)

The Fortran program below calls this function and turns the pointer into a Fortran pointer that behaves as a string of the right length:

program string_pointer
    implicit none

    character(len=:), pointer :: p_string

    call getstring( p_string)
    write(*,*) '>', p_string, '<'
    write(*,*) len(p_string)

contains
subroutine getstring( p_string )
    use iso_c_binding
    character(len=:), pointer :: p_string

    interface
        subroutine getstring_c( c_string, length ) bind(C)
            import :: c_ptr
            type(c_ptr), intent(out) :: c_string
            integer, intent(out)     :: length
        end subroutine getstring_c
    end interface

    type(c_ptr) :: c_string
    integer     :: length

    call getstring_c( c_string, length )

    call c_f_pointer( c_string, p_string )

    p_string => p_string(1:length) ! Would that work? Yes :)
end subroutine getstring

end program string_pointer

I was pleased to see it works. No copy required, no array of individual characters, simply a string. I only hope it is standard-conforming. What are other possibilities to achieve this?

The goal I have in mind: provide an interface to such a C library with a minimal amount of C code.

1 Like

Arjen

The “pattern” you use (return C string as C_PTR and use c_f_pointer to map it to
something you can use in Fortran) is the only one I know that works but thats not
to say there aren’t others. One issue you need to think about though is how and when
do you free the memory allocated in the C function for the string it returns. If you
want to make your function so that it hides the C side as much as possible from
Fortran programmers it might be better to just make a copy of the string (something
you appear to want to avoid) and free the C_PTR returned by the C function inside getstring.
That way you have some protection against memory leaks. This means you will have to make
a C-interop interface for the C free function but thats trivial. You also want to add some logic
to strip C NULL chars.

Also, I didn’t know that you could use a deferred length character pointer that way. Thanks for
showing that, its a good trick to know.

RW

See this thread.

Another option - one I recommend - is better, higher-level code in C; it can be wrappers to existing functions.

#include <string.h>
#include "ISO_Fortran_binding.h"

static char *str = "Hello";

void getstring_c( char **string, size_t *length ) {

     *string = str;
     *length = strlen(*string) ;
}

// Wrapper for Fortran users
int getstr( CFI_cdesc_t *s ) {

    int irc = CFI_establish(s, str, CFI_attribute_pointer, CFI_type_char,
                            strlen(str), (CFI_rank_t)0, NULL);
    return irc;
}

Then the modern Fortran code is simply:

   use, intrinsic :: iso_c_binding, only : c_int, c_char

   interface
      function getstr( str ) result(irc) bind(C, name="getstr")
         import :: c_int, c_char
         implicit none
         ! Argument list
         character(kind=c_char, len=:), pointer, intent(out) :: str
         ! Function result
         integer(c_int) :: irc
      end function 
   end interface

   character(kind=c_char, len=:), pointer :: s
   integer(c_int) :: irc

   irc = getstr( s )
   if ( irc == 0 ) then 
      print *, "s: ", s, "; expected is Hello"
      print *, "len: ", len(s), "; expected is 5"
   else
      print *, "getstr function returned an error."
   end if
   
end 

C:\Temp>cl /c /W3 /EHsc c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.28.29337 for x64
Copyright (C) Microsoft Corporation. All rights reserved.

c.c

C:\Temp>ifort /c /standard-semantics /warn:all /stand:f18 f.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.1.2 Build 20201208_000000
Copyright (C) 1985-2020 Intel Corporation. All rights reserved.

C:\Temp>link f.obj c.obj /subsystem:console /out:f.exe
Microsoft (R) Incremental Linker Version 14.28.29337.0
Copyright (C) Microsoft Corporation. All rights reserved.

C:\Temp>f.exe
s: Hello; expected is Hello
len: 5 ; expected is 5

C:\Temp>

Yes, the issue of freeing the memory is certainly a vexing one. In the case of this library, it is probably better to always return a copy of the sring, so that the memory management is not done in two separate places. The C library knows when to free the C string and on the Fortran side of the interface, it is up to the Fortran program to do the right thing. Mixing up the memory management is asking for trouble.
However, I know that the string is managed nicely by the C library and therefore I could safely leave it to that library. Well, an experiment like I said :slight_smile:

1 Like

Oh, that is nice! I have not used the ISO_Fortran_binding.h stuff yet. I should have a closer look.

The draft for F202X has two functions in the iso_c_binding module to handle converting between Fortran and C strings: C_F_STRPOINTER and F_C_STRING.

Great, that should make it all a lot easier

Another option in the interim is a BLOCK construct:

program string_pointer
   use iso_c_binding
   implicit none
   interface
      subroutine getstring_c( c_string, length ) bind(C)
         import :: c_ptr
         implicit none
         type(c_ptr), intent(out) :: c_string
         integer, intent(out)     :: length
      end subroutine getstring_c
   end interface
   character(kind=c_char, len=:), pointer :: p_string
   type(c_ptr) :: c_string
   integer     :: length

   call getstring_c( c_string, length )
   block
      character(kind=c_char, len=length), pointer :: t_string
      call c_f_pointer( c_string, t_string )
      p_string => t_string
      t_string => null()
   end block
   write(*,*) '>', p_string, '<'
   write(*,*) len(p_string)

end program string_pointer
1 Like

The advantage of that solution is that you avoid a companion C compiler. Ingenious!

1 Like