Return an array of strings from fortran to c++

I have string data in Fortran that I would like to pass to C++.

This is the interface I’m trying to create

module mymod
  use iso_c_binding

  implicit none

contains

  type(c_ptr) function get_names() bind(c)
    use another_mod, only : returns_some_names
    type(c_ptr), dimension(:), allocatable :: string_addresses
    character(len=128), allocatable, target :: names(:)
    integer :: idx

    names = returns_some_names()
    allocate(string_addresses(size(names)))

    do idx = 1, size(names)
      names(idx) = names(idx) // c_null_char
      string_addresses = c_loc(names(idx))
    end do

     get_names = string_addresses

  end function get_names

end module mymod

The corresponding C++ interface would be.

extern "C" char** get_names();

When I compile this, of course I am told “Error: Incompatible ranks 0 and 1 in assignment at (1)” in regards to this line get_names = string_addresses.

I am sure that the answer to this problem exists on the internet but I cannot find it. Can anyone point me in the right direction on how to accept a list of strings from Fortran in C++?

1 Like

Two things stand out. First, string_addresses is an array of C_PTR’s. In your do loop you have

string_addresses = c_loc(names(idx))

this should be

string_addresses(idx) = c_loc(names(idx))

second your function is only returning one C_PTR (associated with the function name) not the whole array. You can try just passing the first array location but that probably won’t work but you never know. ie

get_names = string_address(1)

Not sure how that would be processed on C/C++ side.

1 Like

@kshores ,

Welcome to the Discourse.

As you have noted, the interoperability built into the Fortran standard is with a C companion processor only, and not C++, and thus you have to define the data and interfaces within the extern C scope.

And with C, I suggest you look into enhanced interoperability facilities introduced with Fortran 2018 toward what is of interest to you, as opposed to the older Fortran 2003 way of approaching the data exchange.

You indicate a rectangular array of strings, each of some length N (N=128 in your code snippet). If that is the case, it is rather straightforward to do so with the enhanced interoperability facility:

  • The key aspect here will be to strive for a compact and abstracted code in your Fortran side making full use of standard Fortran features,
  • and do the bit of heavy lifting need in the C interface i.e., the extern C functions in your C++ side
  • Here, make use of the C descriptors defined in ISO_Fortran_binding.h that provide the metadata around your parameters (arguments) in the Fortran procedures. For string arrays, note elem_len of size_t integer kind and extent member of dim member will help you extract the data.

Here’s a simple example with a string array of shape 3 with each string element of length 6. For illustration purposes, this example code makes certain presumptions such as the string array being a Fortran module entity, a getter function, interoperable data types, etc. and last but not least, that you wouldn’t want to make needless copies of the data if there is already a string object on the Fortran side i.e., string array data are not in a named constant in Fortran. Then working with a parameter of POINTER attribute in the getter procedure would make sense to help you prevent the copy.

You can review this example for your understanding, but then you can give it a thought as to how to adapt it for your needs, if such an approach remains of interest to you:

  • Fortran “library” code with the string array in a module
module m
   use, intrinsic :: iso_c_binding, only : c_char
   character(kind=c_char,len=:), allocatable, target, save :: names(:)  !<-- entity holding the string array data
contains
   ! Getter procedure
   subroutine get_names( pnames ) bind(C, name="get_names")
      ! Argument list
      character(kind=c_char,len=:), pointer, intent(inout) :: pnames(:)
      !  Elided are any checks on the state of the data, whether allocated and loaded, etc. 
      pnames => names
   end subroutine
   ! Initializer toward the module entity, may be a database load, read from a file, etc.
   subroutine Finit() bind(C, name="Finit")
      names = [ character(kind=c_char,len=6) :: c_char_"red",   &
                                                c_char_"green", &
                                                c_char_"blue" ]
   end subroutine
end module
  • C++ caller
#include <iostream>
#include <string>
using namespace std;
#include "ISO_Fortran_binding.h"

extern "C" {
   // Prototype for the Fortran procedures
   void Finit(void);
   void get_names( CFI_cdesc_t * );
}

int main()
{

   Finit();

   // Use macro from ISO_Fortran_binding to set aside an address to "describe" the string data
   CFI_CDESC_T(1) names;
   char *s;

   // Call the Fortran getter for the string array data description
   get_names((CFI_cdesc_t *)&names);

   // Extract the data from the C descriptor toward the string array
   s = (char *)names.base_addr;

   for (int i = 0; i < names.dim[0].extent; i++) {
       for (int j = 0; j < names.elem_len; j++) {
           cout << s[i*names.elem_len+j];
       }
       cout << endl;
   }

   return (0);

}
  • Program response using Intel Fortran and Microsoft C/C++ compiler on Windows
C:\temp>ifort /c /standard-semantics m.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.8.0 Build 20221119_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.


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

c++.cpp
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): warning C4200: nonstandard extension used: zero-sized array in struct/union
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): note: This member will be ignored by a defaulted constructor or copy/move assignment operator

C:\temp>link c++.obj m.obj /subsystem:console /out:c++.exe
Microsoft (R) Incremental Linker Version 14.31.31105.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c++.exe
red
green
blue

Note: I reckon there is a bug in gfortran with the extent member not being filled out correctly. If you are a gfortran user, you may want to post at GCC Bugzilla.

P…S.> My first post had the int irc = 0 line in the C++ called code just prior to the line with Finit()invocation; and had return(irc) as the last statement. In a subsequent edit, I inadvertently deleted the irc declaration but retained the return statement. It’s now edited to just return(0).

2 Likes

Woah, fantastic answer! This certainly seems right in line with what I’m wanting. Thank you so much for your effort here.

Note with this “debug print” included in the C++ caller:

..
   // set outstring to base address of C descriptor
   s = (char *)names.base_addr;

   cout << "names.dim[0].extent = " << names.dim[0].extent << "; expected is 3" << endl;
..

The program response using gfortran on Windows OS (gcc version 13.0.1 20230122 (experimental) (GCC)) is as follows:

C:\temp>gfortran c++.cpp m.f90 -lstdc++ -o c++.exe

C:\temp>c++.exe
names.dim[0].extent = 0; expected is 3

Intel Fortran with Microsoft C/C++ compiler leads to

C:\temp>ifort /c /standard-semantics m.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.8.0 Build 20221119_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.


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

c++.cpp
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): warning C4200: nonstandard extension used: zero-sized array in struct/union
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): note: This member will be ignored by a defaulted constructor or copy/move assignment operator

C:\temp>link c++.obj m.obj /subsystem:console /out:c++.exe
Microsoft (R) Incremental Linker Version 14.31.31105.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c++.exe
names.dim[0].extent = 3; expected is 3
red
green
blue

@kshores ,

If you are able to use a C++17 or later compiler, I suggest you use <string_view> if this “array” of strings is going to “live” in the Fortran side of your code. You might find it rather convenient to work with:

#include <vector>
#include <string_view>
#include <iostream>
#include "ISO_Fortran_binding.h"
using namespace std;

extern "C" {
   // Prototype for the Fortran procedures
   void Finit(void);
   void get_names( CFI_cdesc_t * );
}

int main()
{

   std::vector<std::string_view> vs;

   Finit();

   // Use macro from ISO_Fortran_binding to set aside an address to "description" of string data
   CFI_CDESC_T(1) names;

   // Call the Fortran procedure for string manipulation
   get_names((CFI_cdesc_t *)&names);

   for (int i = 0; i < names.dim[0].extent; i++) {
       vs.push_back(std::string_view((char *)names.base_addr).substr(i * names.elem_len, names.elem_len));
   }
   for (int i = 0; i < names.dim[0].extent; i++) {
       cout << vs[i] << endl;
   }

   return (0);
}
C:\temp>cl /c /std:c++20 /W3 /EHsc c++.cpp
Microsoft (R) C/C++ Optimizing Compiler Version 19.34.31937 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c++.cpp
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): warning C4200: nonstandard extension used: zero-sized array in struct/union
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): note: This member will be ignored by a defaulted constructor or copy/move assignment operator

C:\temp>link c++.obj m.obj /subsystem:console /out:c++.exe
Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c++.exe
red
green
blue
1 Like

Hi @FortranFan

Thank you so very much for all of this. I had seen the ISO_Fortran_binding C header before but wasn’t quite sure how to use it.

This is exactly what I needed and on my machine everything works with gfortran. My version of gfortran, GNU Fortran (Homebrew GCC 12.2.0) 12.2.0, does not seem to have the same issue that yours does so maybe that issue is Windows specific.

1 Like

It’s worth noting I had to add this:

CFI_CDESC_T(1) names;

CFI_establish((CFI_cdesc_t *)&names, NULL,
                    CFI_attribute_pointer,
                    CFI_type_char, 0, (CFI_rank_t)1, NULL);

get_names((CFI_cdesc_t *)&names);

A full C program:

#include <vector>
#include <string_view>
#include <iostream>
#include "ISO_Fortran_binding.h"
using namespace std;

extern "C" {
   // Prototype for the Fortran procedures
   void Finit(void);
   void get_names( CFI_cdesc_t * );
}

int main()
{

   std::vector<std::string_view> vs;

   Finit();

   // Use macro from ISO_Fortran_binding to set aside an address to "description" of string data
   CFI_CDESC_T(1) names;

  CFI_establish((CFI_cdesc_t *)&names, NULL,
                    CFI_attribute_pointer,
                    CFI_type_char, 0, (CFI_rank_t)1, NULL);

   // Call the Fortran procedure for string manipulation
   get_names((CFI_cdesc_t *)&names);

   for (int i = 0; i < names.dim[0].extent; i++) {
       vs.push_back(std::string_view((char *)names.base_addr).substr(i * names.elem_len, names.elem_len));
   }
   for (int i = 0; i < names.dim[0].extent; i++) {
       cout << vs[i] << endl;
   }

   return (0);
}

Using this without CFI_establish worked in most cases. However, adding the compiler flag -fcheck=bounds caused this function to break, unless I added a call to CFI_establish.

The error without CFI_establish was along these lines:

Fortran runtime error: Unexpected version 16 (expected 1) in CFI descriptor passed to dummy argument pnames

I wonder if the global module variable names gets deallocated at program exit? Since it has the save attribute it probably doesn’t, and the resources get reclaimed by the operating system when the program terminates.

While not strictly related to this thread, what happens in this example:

void foo(void) {
{
   // ...
   {
      CFI_CDESC_T(1) array;

      int stat;
      stat = CFI_establish( (CFI_cdesc_t *) &array, NULL, CFI_attribute_allocatable, ... );

      CFI_index_t lb[1], ub[1];
      lb[0] = 1; ub[0] = n;
      stat = CFI_allocate(CFI_cdesc_t *) &array, lb, ub, 0);
   }
   // ...
}

Is the array deallocated when we exit the defining C scope, or should we do it manually?

I’m betting the array is definitely not deallocated upon exiting the scope. See this gcc implementation of CFI_allocate. After a bunch of checks there’s a calloc. So, to my understanding, the snippet above would leak memory.

In the examples provided by @FortranFan, all of the memory for the characters live in Fortran so there would be no reason (or sense) in deallocating the memory.

Good feedback for anyone who might face the issue with the compiler.

In principle, it should not be needed but including it won’t hurt, kind of like initializing an actual argument to a procedure that defines it anyway.

1 Like

I’m not certain, but I would think so too. The automatic deallocation thing is a feature of the fortran language, so once you step over into the C side of things, things will likely work like they do in C, not fortran.

It might be good to see some confirmation of this from the compiler writers here. If I’m wrong, and the array does get deallocated automatically, that would be a very useful thing to know.

I filed an issue with gcc and the respondent there seems to believe it is required. If this is really a compiler bug, perhaps you might have more insight that you could share with the gcc maintainers than I do. Just an FYI

1 Like

Yeah interoperability has its limits. I wonder if one could make a conforming CFI_CDESC_T which would use a smart pointer under the hood to prevent memory leaks via reference-counting.

I was reading A Tour of C++ (Third edition, C++20) and noticed a pattern for object destruction by passing a lambda to a class. With a heap-allocated C pointer it might look as follows:

double *x = malloc( n*sizeof(double) );
auto action = finally([=](){ free(x); }); // (so many brackets...)

The idea is to invoke the lambda via the destructor of a small helper class:

// Adapted from gsl-lite.h (https://github.com/gsl-lite/gsl-lite)
//
// (see also C.30 in C++ Core Guidelines, 
//     https://isocpp.github.io/CppCoreGuidelines/CppCoreGuidelines)
// 
template<typename Action>
class final_action
{
public:
    final_action( Action action )
    : action_( action ) {}

    ~final_action()
    {
        action_();
    }

private:
    Action action_;
};

template< class Fn >
[[nodiscard]] auto finally( Fn const & f )
{
    return final_action(( f ));
}

You can adapt the concept to a Fortran allocatable array:

void foo(int n)
{
    CFI_CDESC_T(2) samples_;
    const auto samples = (CFI_cdesc_t *) &samples_;

    CFI_establish( /* ... */ );

    // Make sure we don't forget to deallocate
    auto dealloc = finally([&]{
        if (samples->base_addr) {
            CHECK_CFI( CFI_deallocate(samples) )
        }
    });

    bar(samples); // Allocation in Fortran, samples is intent(out)

    // ...

} // dealloc called here

For fun I decided to implement a complete example which approximates the value of π by dart throwing (Monte-Carlo). The Fortran version is very dense:

! sampling.f90
!
module sampling
   use, intrinsic :: iso_c_binding, only: &
      ip => c_int, dp => c_double
   implicit none
   private
contains
   ! Draw random samples in the unit square [0,1)^2
   subroutine draw_random_samples(n,samples) bind(c)
      integer(ip), intent(in), value :: n
      real(dp), allocatable, intent(out) :: samples(:,:)
      allocate(samples(n,2))
      call random_number(samples)
   end subroutine
   ! Estimate pi (3.14159...) by dart throwing
   function f_estimate_pi(n) bind(c) result(pi)
      integer(ip), intent(in), value :: n
      real(dp) :: pi
      real(dp), allocatable :: samples(:,:)
      integer :: ncirc
      call draw_random_samples(n,samples)
      associate(x => samples(:,1), y => samples(:,2))
         pi = 4 * real(count(x**2 + y**2 < 1, dim=1), dp) / n
      end associate
   end function
end module

In the C++ version I reused the sampling procedure. For the the counting part I decided to use ranges and views for the first time (requires C++20):

/* Calculate pi using the Monte-Carlo method.
 *
 * Random numbers are generated in Fortran just for the 
 * sake of testing the F2018 enhanced C interoperability.
 */
double estimate_pi(int n)
{
    CFI_CDESC_T(2) samples_;
    const auto samples = (CFI_cdesc_t *) &samples_;

    CHECK_CFI( CFI_establish(samples,
                             NULL,
                             CFI_attribute_allocatable,
                             CFI_type_double,
                             0 /* ignored */,
                             (CFI_rank_t) 2,
                             NULL /* ignored */) )

    // Make sure we don't forget to deallocate
    auto dealloc = finally([&]{
        if (samples->base_addr) {
            CHECK_CFI( CFI_deallocate(samples) )
        }
    });

    draw_random_samples( n, samples); 

    auto inside_of_circle = [=](int i){
        // <!> Pointer arithmetic <!>
        const double x = *( (double *) samples->base_addr + i);
        const double y = *( (double *) samples->base_addr + i + n);
        return x*x + y*y < 1;
    };

    using std::ranges::count_if;
    using std::views::iota;

    int ncircle = count_if( iota( 0, n-1 ), inside_of_circle );

    return 4.0 * ((double) ncircle) / n;

} // dealloc called here

The full example is given below:

Makefile
FC  = gfortran
CXX = g++

FCFLAGS  = -Wall -O2 -march=native -std=f2018
CXXFLAGS = -Wall -O2 -march=native -std=c++20
 
LDFLAGS  = -lgfortran

picalc: picalc.cpp sampling.o
	$(CXX) $(CXXFLAGS) -o $@ $^ $(LDFLAGS)

sampling.o sampling.mod: sampling.f90
	$(FC) $(FCFLAGS) -c $<

.phony: clean

clean:
	rm *.o *.mod picalc
sampling.f90
! sampling.f90
!
module sampling
   use, intrinsic :: iso_c_binding, only: &
      ip => c_int, dp => c_double
   implicit none
   private
contains
   ! Draw random samples in the unit square [0,1)^2
   subroutine draw_random_samples(n,samples) bind(c)
      integer(ip), intent(in), value :: n
      real(dp), allocatable, intent(out) :: samples(:,:)
      allocate(samples(n,2))
      call random_number(samples)
   end subroutine
   ! Estimate pi (3.14159...) by dart throwing
   function f_estimate_pi(n) bind(c) result(pi)
      integer(ip), intent(in), value :: n
      real(dp) :: pi
      real(dp), allocatable :: samples(:,:)
      call draw_random_samples(n,samples)
      associate(x => samples(:,1), y => samples(:,2))
         pi = 4 * real(count(x**2 + y**2 < 1, dim=1), dp) / n
      end associate
   end function
end module

picalc.cpp

#include <iostream>
#include <cstdio>
#include <cstdlib>

#include <span>
#include <ranges>
#include <algorithm>

#include <ISO_Fortran_binding.h>

static const char *cfi_errstrs[12] = {
    "No error detected.\n",
    "The base address member of a C descriptor is a null pointer in a context that requires a non-null pointer value.\n",
    "The base address member of a C descriptor is not a null pointer in a context that requires a null pointer value.\n",
    "The value supplied for the element length member of a C descriptor is not valid.\n",
    "The value supplied for the rank member of a C descriptor is not valid.\n",
    "The value supplied for the type member of a C descriptor is not valid.\n",
    "The value supplied for the attribute member of a C descriptor is not valid.\n",
    "The value supplied for the extent member of a CFI_dim_t structure is not valid.\n",
    "A C descriptor is invalid in some way.\n",
    "Memory allocation failed.\n",
    "A reference is out of bounds.\n",
    "Unrecognized status code.\n"
};

// Returns the description string for an error code.
//
const char* cfiGetErrorString(int stat) {

    switch (stat) {
        case CFI_SUCCESS:                  return cfi_errstrs[0]  ; break; 
        case CFI_ERROR_BASE_ADDR_NULL:     return cfi_errstrs[1]  ; break;
        case CFI_ERROR_BASE_ADDR_NOT_NULL: return cfi_errstrs[2]  ; break;
        case CFI_INVALID_ELEM_LEN:         return cfi_errstrs[3]  ; break;
        case CFI_INVALID_RANK:             return cfi_errstrs[4]  ; break;
        case CFI_INVALID_TYPE:             return cfi_errstrs[5]  ; break;
        case CFI_INVALID_ATTRIBUTE:        return cfi_errstrs[6]  ; break;
        case CFI_INVALID_EXTENT:           return cfi_errstrs[7]  ; break;
        case CFI_INVALID_DESCRIPTOR:       return cfi_errstrs[8]  ; break;
        case CFI_ERROR_MEM_ALLOCATION:     return cfi_errstrs[9]  ; break;
        case CFI_ERROR_OUT_OF_BOUNDS:      return cfi_errstrs[10] ; break;
    }

    return cfi_errstrs[11];
}

#define CHECK_CFI(func)                                                        \
{                                                                              \
    int stat = (func);                                                         \
    if (stat != CFI_SUCCESS) {                                                 \
        fprintf(stderr,"%s:%d: CFI API failed with error: (%d) %s",            \
            __FILE__, __LINE__, stat, cfiGetErrorString(stat));                \
    }                                                                          \
}                                                                              \

template<typename Action>
class final_action
{
public:
    final_action( Action action )
    : action_( action ) {}

    ~final_action()
    {
        action_();
    }

private:
    Action action_;
};

template< class Fn >
[[nodiscard]] auto finally( Fn const & f )
{
    return final_action(( f ));
}

// 
namespace stdv = std::views;
namespace stdr = std::ranges;

// Draws random samples in the unit square [0,1)^2
//
// Arguments:
// [in]        n: the number of samples
// [out] samples: an array of (x,y) values, shape [n,2]
//
extern "C" void draw_random_samples(int n, CFI_cdesc_t *samples);

// Same procedure as the one below, but implemented in Fortran
extern "C" double f_estimate_pi(int n);

/* Calculate pi using the Monte-Carlo method.
 *
 * Random numbers are generated in Fortran just for the 
 * sake of testing the F2018 enhanced C interoperability.
 */
double estimate_pi(int n)
{
    CFI_CDESC_T(2) samples_;
    const auto samples = (CFI_cdesc_t *) &samples_;

    CHECK_CFI( CFI_establish(samples,
                             NULL,
                             CFI_attribute_allocatable,
                             CFI_type_double,
                             0 /* ignored */,
                             (CFI_rank_t) 2,
                             NULL /* ignored */) )

    // Make sure we don't forget to deallocate
    auto dealloc = finally([&]{
        if (samples->base_addr) {
            CHECK_CFI( CFI_deallocate(samples) )
        }
    });

    draw_random_samples( n, samples); 

    auto inside_of_circle = [=](int i)
    {
        // <!> Pointer arithmetic <!>
     
        const double x = *( (double *) samples->base_addr + i);
        const double y = *( (double *) samples->base_addr + i + n);
        
        return x*x + y*y < 1;
    };

#if 0 
    //
    // Old-fashioned approach
    //
    int ncircle = 0;
    for (int i = 0; i < n; ++i) {
        if (inside_of_circle(i)) ncircle++;
    }    
#else
    //
    // Modern approach with views and ranges
    //
    using std::ranges::count_if;
    using std::views::iota;

    int ncircle = count_if( iota(0,n-1), inside_of_circle );
#endif

    return 4.0 * ((double) ncircle) / n;

} // dealloc called here

int main(int argc, char const *argv[])
{
    if (argc != 2) {
        std::cout << "Usage: ./picalc N\n";
        return 1;
    }

    const int N = atoi(argv[1]);

    std::cout << "pi = " <<   estimate_pi( N ) << '\n';
    std::cout << "pi = " << f_estimate_pi( N ) << '\n';

    return 0;
}
2 Likes

@ivanpribec ,

Nice, you are in effect laying down the early seeds for interoperability for Fortran with modern C++!

You may want to seriously investigate/research the possible semantics of bind(C++) in the standard which take advantage of Fortran ALLOCATABLEs with suitable RAII memory mapping features in modern C++. It will be a brilliant paper to publish too.

2 Likes