Fixed-length string from C++ to Fortran

Hello,

I’m trying to pass a fixed-length string from C++ to Fortran, similar to what is shown below for a variable-length string. I guess the difficulty here is heap vs stack, so a solution without copying might not be possible.

Does anyone has any good ideas for that?

! main.f90
program main

use, intrinsic :: ISO_C_binding, only: C_INT, C_CHAR

implicit none

interface

  subroutine uuid_CPP(uuid, stat) bind(C)
    use, intrinsic :: ISO_C_binding, only: C_INT, C_CHAR

    character(kind=C_CHAR,len=:), allocatable, intent(out) :: uuid
    integer(C_INT),                            intent(out) :: stat
  end subroutine uuid_CPP

end interface

character(kind=C_CHAR,len=:), allocatable :: uuid_str

uuid_str = UUID()

print*, uuid_str

contains

function UUID()

  character(kind=C_CHAR,len=:), allocatable :: UUID

  integer(C_INT) :: stat


  call uuid_CPP(UUID,stat)
  if (stat /= 0) error stop 'could not get UUID'

end function UUID

end program main
// uuid.cpp
#include "ISO_Fortran_binding.h"
#include <boost/uuid/uuid.hpp>
#include <boost/uuid/uuid_io.hpp>
#include <boost/uuid/uuid_generators.hpp>
#include <boost/lexical_cast.hpp>

extern "C" void uuid_cpp(CFI_cdesc_t *uuid, int *stat);

void uuid_cpp(CFI_cdesc_t *uuid, int *stat){
  const std::string uuid_tmp = boost::lexical_cast<std::string>(boost::uuids::random_generator()());
  const char *uuid_c = uuid_tmp.c_str();
  if (CFI_allocate(uuid, (CFI_index_t *)0, (CFI_index_t *)0, strlen(uuid_c)) == 0){
    memcpy(uuid->base_addr, uuid_c, strlen(uuid_c));
    *stat = 0;
  }
  else *stat = 1;
}

build and run with

gcc -c uuid.cpp
gfortran -c main.f90
gfortran uuid.o main.o -lstdc++
./a.out

What about passing 16 byte array to C++ code to fill it with UUID bytes, then in Fortran print those bytes into a character string. This way, both byte array and resulting char string could live in Fortran code on the stack.

The issue I face with gfortran (version 15.1) is that I can’t define the character to have a fixed length:

Error: Character dummy argument ‘uuid’ at (1) must be of constant length of one or assumed length, unless it has assumed shape or assumed rank, as procedure ‘get_uuid_cpp’ has the BIND(C) attribute

for

    subroutine get_uuid_CPP(uuid, stat) bind(C)                                                      
      use, intrinsic :: ISO_C_binding, only: C_INT, C_CHAR                                           
                                                                                                     
      character(kind=C_CHAR,len=16), intent(out) :: uuid                                             
      integer(C_INT),                intent(out) :: stat                                             
    end subroutine get_uuid_CPP                                                                      
                                                                                                     
  end interface

Don’t pass one 16-char entity, but instead pass array of 1-byte entities. Perhaps integer(c_int8_t), dimension(*) :: uuid. In C code, you should get int8_t* uuid that you can fill with 16 bytes of binary values by accessing uuid[0] through uuid[15].

Could even pass integer(c_int32_t), value :: uuid_len to get_uuid_CPP() for additional length sanity check.

1 Like