Iso_c_binding: interface to a C function returning a string

I don’t see anything wrong in your implementation. Have you tested it with other compilers?

One difference is the use of auto-allocation on assignment. You could try with to see if that leads to a correct descriptor:

allocate(str, source=str_ptr)

A potential issue (bug) is the use of the same name for Fortran and C symbols (xbsf_get_error_string); this should not be a problem due to the Fortran name mangling, but I remember encountering a similar issue before.

OK, I was unsure…

If the string is still zero-length with my code, then it means that for some reason strlen_c(cstr) has returned the value 0.

Mh, yeah, but clearly not the case. In any case, I even tried changing the Fortran function name to be double sure, same behavior.

I am not sure if I correctly understand your message, but in any case, to be as clear as possible, within the Fortran xbsf_get_error_string function eevrything works as expected, and the allocatable result string is allocated to a non-0 length string, containing the correct message.
I think it is the immediately following result assignment which is failing to keep the constructed result dummy variable descriptor to the actual variable.

Console output:

 "GPU Offloading not supported"          28  # This is the print line in `xbsf_get_error_string`
   --[info]   ""           0    # This is a print after the function result assignment at the caller site.

I think you’d need the -1 in case you are constructing a C-interoperable Fortran string IN a Fortran unit, since the c_null_char is then interpreted as a valid char in the string representation from a pure Fortran POV (after which another internal null char is added by the compiler to adhere to its length, EDIT: this might be incorrect, I am not sure actually):

character(len = :, kind=c_char), allocatable, target :: f_c_like_str

f_c_like_str = c_char_"hello" // c_null_char
print *, len(f_c_like_str)   ! Prints 6
print *, strlen_c(c_loc(f_c_like_str))   ! Prints 5

Does the result change if the function

   module function xbsf_get_error_string(ierr) result(str)
      integer(xbsf_int_t), value :: ierr
      character(len = :), allocatable :: str

is replaced by a subroutine (such that str is passed as an actual argument)? Also, in the function case, does it work correctly if the result variable is declared as a character string of fixed size (say, character(100) :: str)? I remember I saw a similar issue for allocatable strings in the context of recursive functions or OpenMP. Because it might also affect other cases, I think it would be great if a reproducible code example could be created (e.g. for submission to the gfortran issue site).

1 Like

Could you post the code of xbsf_get_error_string ?

Not sure if this helps, but I believe the C standard function returns a size_t, not an int, so if you’re on a 64-bit platform you may receive only the first 32 bits and they may all be zeroes…?

1 Like

Yes, changing to a subroutine fixes the issue. So, even more likely there’s an issue with gfortran-12 in assigning the return value of an allocatable character function.

It’s as simple as:

static const char *error_strings[] = {
   "...",
};
const char *xbsf_get_error_string(const int err) { return error_strings[err]; }

Oh, yes, nice catch, though it did not really fix the issue. Moreover, it’s very unlikely the length of a string to be > 2^(32+x) with with x>0, is it?

1 Like

A MRE would help us helping you, probably :slight_smile:

Mh, this follows the same structure but seems to work :thinking:

// c.c
const char *c_arr[] = {
    "Hello",
};

const char *get_c_string(void) { return c_arr[0]; }
program test
   use :: iso_c_binding
   implicit none
   character(len = :), allocatable :: str

   str = get_string_f()
   print *, str

contains

   function get_string_f() result(str)
      character(len = :), allocatable :: str
      type(c_ptr) :: cstr
      integer(c_size_t) :: cstr_len

      interface
         function get_string_c() result(ptr) bind(c, name="get_c_string")
            import :: c_ptr
            type(c_ptr) :: ptr
         end function
         function strlen_c(ptr) result(l) bind(c, name="strlen")
            import :: c_ptr, c_size_t
            type(c_ptr), value :: ptr
            integer(c_size_t) :: l
         end function
      end interface

      cstr     = get_string_c()
      cstr_len = strlen_c(cstr)
      block
         character(len = cstr_len, kind = c_char), pointer :: str_ptr

         call c_f_pointer(cstr, str_ptr)
         allocate(str, source=str_ptr)
      end block
      print *, '"', str, '"', len(str), allocated(str)
   end function
end program

Though still not sure, if the strange behavior of gfortran comes from the following potential bug (mentioned in the bugzilla page above)

> typedef character(kind=1) struct
> character(kind=1)[1:slen.1][1:slen.1];
> pstr.2 = 0B;
> slen.1 = 0;
Maybe the order here. slen.1 should be set to 0
before the use inside the typedef. That is kinda of the reason
why static works (with not openmp).

I guess the behavior of this bug may depend strongly on the actual code if it uses an uninitialized variable internally (like slen.1). Then, it might be less straightforward to make a minimal reproducer (than expected)…

Anyway, because I also use functions that return an allocatable string (for converting ints and reals to strings, currently using gfortran-11), I am also worried about the above issue.

1 Like

This comment would apply with little-endian addressing conventions, but not big-endian conventions. That’s probably true on most os+compilers these days. With big-endian conventions, it would be the address of the most significant bits in the 64-bit integer that is passed as an argument, and the high-order 32 bits would then define the value.

1 Like

There is a related discussion on the J3 mailing list: [J3] Question global identifiers, where Malcolm Cohen writes you cannot have global identifiers with the same name.

e.g.

! global identifier collision

function xbsf_get_error_string(ierr) result(str)
! ...
     interface
         function xbsf_get_error_string_c(err) result(cptr) bind(c, name="xbsf_get_error_string")
            import :: c_int, c_ptr
            integer(c_int), value :: err
            type(c_ptr) :: cptr
         end function
     end interface
! ...
end function

In your case xbsf_get_error_string() is a module function and that is supposedly okay.

1 Like