Issues interfacing between C++ and Fortran

I am working on an interface to the nanoflann library for N-nearest neighbor searches in two- and three-dimensions. This is a header-only library written in C++.

I have faced a few issues in the process, and would appreciate help from the community to establish what are the “healthy” practices:

  1. Interfacing between Fortran logical and C++ bool type

    I want to interface to the following C++ class method (the class details are not relevant):

      inline bool full() const { return count == capacity; }
    

    My first approach was to use the corresponding C bool macro, giving me the interface:

    bool nanoflann_KNNResultSet_full(KNNResultSet_t *rs);
    

    (The pointer *rs is supposed to be an instance of the class I’m wrapping.)

    According to a thread on Stack Overflow, the size of the C++ bool and the C bool are potentially incompatible on some compilers or might depend upon the build process. This lead me to consider mapping the C++ bool to the C int in the intermediate C layer. In the Fortran wrapper I can then map the C int back to the default logical type using the following if clause:

    ! The C header (internally maps the C `bool` to 0 or 1)
    ! int nanoflann_KNNResultSet_full(KNNResultSet_t *rs);
    
    ! Fortran mapping back to default logical kind
    if (nanoflann_KNNResultSet_full(rs) > 0) then
      result = .true.
    else
      result = .false
    end if
    

    Has anyone encountered issues when interfacing between bools before? Is the mapping of C++ bool to a C int (0,1) preferred over the mapping to the C bool? I am also not a fan of having to carry logical(c_bool) around in my Fortran layer.

  2. Correct way to wrap a C++ object into C

    This issue is not related to Fortran per se. I was confused by the numerous different approaches to flatten a C++ object for consumption in C. The multiple threads on Stack Overflow and other resources contain somewhat contradicting information.

    I tried following the approach used in symengine/cwrapper.h and symengine/cwrapper.cpp initially (@certik), but ran into memory alignment problems. Instead, I ended up using the approach demonstrated in this blog post. If I understand correctly, by casting the C++ objects into void * we loss the type safety of C++. However, once I wrap the C layer back into Fortran I can reestablish the type safety. I was wondering if someone has some further tips and resources on this topic? The case study given in the book by Damian Rouson on producing the Fortran Trilinos wrapper, seems already a bit outdated.

  3. View into memory of a C++ object

    In part of the nanoflann library, the user is supposed to pass an instance of a std::vector<std::pair<int,double>> to the constructor of a C++ class. This vector is then used internally as a dynamic storage container for index and distance pairs found during a radius search. The definition of the class is the following:

    template <typename _DistanceType, typename _IndexType = size_t>
    class RadiusResultSet {
    public:
      typedef _DistanceType DistanceType;
      typedef _IndexType IndexType;
    
    public:
      const DistanceType radius;
    
      std::vector<std::pair<IndexType, DistanceType>> &m_indices_dists;
    
      inline RadiusResultSet(
          DistanceType radius_,
          std::vector<std::pair<IndexType, DistanceType>> &indices_dists)
          : radius(radius_), m_indices_dists(indices_dists) {
        init();
      }
    
      // ...
    }
    

    I was wondering if an array of struct Pair { int idx; double pair}; objects could be mapped to the memory of the C++ std::vector<std::pair<int,double>> instance &m_indices_dists? I thought this might be a way to make this object interoperable with a fortran array of type

    type, bind(c) :: pair
      integer(c_int) :: idx
      real(c_double) :: pair
    end type
    

    Since I could not find sufficient information to determine if this works, I decided to take the safe (but wasteful) approach of copying the data from the C++ object to Fortran arrays I allocate in the C wrapper layer using the tools from ISO_Fortran_binding.h header file. The C prototype is then

    void nanoflann_RadiusResultSet_getResultPairs(RadiusResultSet_t *rs, CFI_cdesc_t *idxs, CFI_cdesc_t *dists, int* stat);
    

    and the corresponding Fortran interface is

    subroutine nanoflann_RadiusResultSet_getResultPairs(rs,idxs,dists,stat) &
      bind(c,name="nanoflann_RadiusResultSet_getResultPairs")
      use, intrinsic :: iso_c_binding, only: c_ptr, c_double, c_int
      type(c_ptr), intent(in), value :: rs
      integer(c_int), intent(inout), allocatable :: idxs(:)
      real(c_double), intent(inout), allocatable :: dists(:)
      integer(c_int), intent(out), optional :: stat
    end subroutine
    

    This interface would be much simpler, had the C++ developers used two separate lists instead of a list of pairs as their storage container, i.e.:

      inline RadiusResultSet(
          DistanceType radius_,
          std::vector<IndexType> &indices, std::vector<DistanceType> &dists)
          : ...
    

    In this case I could have easily recovered pointers to the underlying std::vector data using the methods indices.data(), indices.size() (and analogously for the dists vector), saving myself one copy in the Fortran layer.

I would appreciate any answers or comments!

If anyone has experience using tools such as shroud or swig-fortran, I would be happy to hear their opinion. Can these tools also wrap templated classes?

Regarding bool, the standard would have you use logical(c_bool). At least one compiler (ifort) would require you to use an option (-standard-semantics or -fpscomp logicals) to get the 0/not-0 interpretation.

This assumes C - I am quite taken aback at the notion that C and C++ would have different interpretations of bool.

As you allude to, you’ll need an intermediate layer in C (e.g., with extern) to work with Fortran (i.e., assuming you plan to stick to standard Fortran and not use some compiler-specific extensions). And in this layer, if you use _Bool (or the bool macro from “stdbool.h”) as the interoperating type with Fortran, chances are rather high you will not face an issue. After all, the size is really all matters when it comes to this type. On the C++ side, its standard sees bool as an integral type anyway and it slates this type also for promotions (and conversions) which most compilers do safely…

1 Like

I personally think that is the only approach that is viable in terms of 2 considerations important to me: a) be standard-conforming and b) be readable and maintainable even if it involves verbosity.

Here’s an example with the opaque (void *) pointer I had provided on another forum a while ago.

Thanks @FortranFan and @sblionel for your previous answers.

Just to confirm my understanding of the mixed-language linking process, I have a question related to the following scenario.

Assume I have a C++ library in the file foo.cpp, containing a number of (public) procedures wrapped in an extern "C" scoping block. I would like to use these procedures in a Fortran program. The procedure prototypes are also declared in the file foo.h (included in foo.cpp). The file foo.h also uses a #ifdef guard to guarantee the right compiler name mangling were the header included in other C or C++ source files.

#ifdef __cplusplus
extern "C" {
#endif

void foo1(...);
void foo2(...);
int foo3(...);

#ifdef __cplusplus
}
#endif

Now to the Fortan side. The module foo_interface in file foo_interface.f90 declares interfaces for the ˙"C"˙ functions using the bind(C) attributes. Finally the fooX functions are used by a main program located in main_foo.f90.

Is a C compiler needed to arrive at an executable at all? According to my current understanding it isn’t. I just need the sequence:

g++ -I./ -c foo.cpp  # include current folder for the header file
gfortran -c foo_interface.f90
gfortran -c main_foo.f90
gfortran foo.o foo_interface.o main_foo.o -lstdc++ # foo needs C++ stdlib

Essentially the linker takes care of correctly linking the C++ and Fortran binaries.


Now for a second question related to a lifetime of C descriptors.

Assume the function foo1 has the following prototype:

void foo1(void *cpp_object, const CFI_cdesc_t *fortran_array);

and has the purpose of initializing a C++ class, which stores a reference to the Fortran array. A pointer to the newly created C++ class instance is returned in *cpp_object.

Upon return from foo1, is the pointer to the C descriptor *fortran_array inside of cpp_object still a valid object? At least according to my current experience, the C descriptor seems to become corrupt in subsequent calls.

What I am trying to achieve is essentially a C++ class which “shadows” a Fortran array. Perhaps an illustration in the Fortran side should help clarify:

subroutine use_foo()
   type(c_ptr) :: cpp_object = c_null_ptr
   real, allocatable :: a(:,:)

   allocate(a(3,1000))
   call random_number(a)

   ! initalize cpp_object which stores reference to array a
   call foo1(cpp_object,a)

   ! cpp_object uses array to calculate res1 and res2
   call foo2(cpp_object,res1,res2)

   ! destroy cpp_object
   call foo3(cpp_object)

   ! array a is deallocated automatically
end subroutine

Hi @ivanpribec, regarding your second question, have you checked that cpp_object is still valid after foo1? I only ask because you mention returning a pointer to cpp_object from foo1 but I had thought you required double-pointers (pointer-to-pointer) to do such a thing in c? Apologies if I have the wrong idea, it’s been a while since I l’ve subjected myself to c pointers :sweat_smile:.

Regarding your first question, your explanation agrees with my own understanding for the process.

1 Like

When you use a compiler verb (gfortran, gcc, ifort, etc.) to link, the driver usually appends a set of language libraries typically needed for its language. Most of the time this also includes C or C++ libraries, but your C++ code might need a library the Fortran driver wouldn’t include. If so, you’ll figure that out soon enough, and will then have to add a -l to name the appropriate library (or libraries.)

1 Like

I’ve created a minimum working example of my problem:

foo.h:

#ifndef FOO_H_
#define FOO_H_

#include "ISO_Fortran_binding.h"

#ifdef __cplusplus
extern "C" {
#endif

struct CPP_UsesFortranArray;
typedef struct CPP_UsesFortranArray CPP_UsesFortranArray_t;

void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const CFI_cdesc_t *array);

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr);

void print_array_and_maxval(const CFI_cdesc_t *array);

#ifdef __cplusplus
}
#endif

#endif // FOO_H_

I followed your advice with the double pointer and the constructor works even though I am not 100 % sure why. :+1:

foo.cpp:

#include "foo.h"

#include <iostream>
#include <cmath>

template <typename T>
struct FortranArray {

  typedef T real_t;

  // A const reference to rank 1 Fortran array
  // (can be discontiguous but with regular strides)
  const CFI_cdesc_t *obj;

  // Constructor
  FortranArray(const CFI_cdesc_t *obj_) : obj(obj_) {
    std::cout << "In FortranArray Constructor: " << std::endl;
    for (size_t i = 0; i < this->size(); i++) {
      std::cout << "obj[" << i <<"] = " << this->operator()(i) << std::endl;
    }
  }

  // Returns the i'th element of the vector
  inline T operator()(const size_t i) const {
    char *elt = (char *) obj->base_addr;
    elt += (i*obj->dim[0].sm);
    return *(T *) elt;
  }

  inline size_t size() const {
    return obj->dim[0].extent;
  }
};

template <typename ArrayType>
class UsesFortranArray {

  const ArrayType &array; // Reference to a Fortran array

  typedef typename ArrayType::real_t real_t;

public:

  // Constructor
  UsesFortranArray(const ArrayType &inputArray) :
    array(inputArray) {
      std::cout << "In UsesFortranArray Constructor" << std::endl;
      this->maxval();
    }

  real_t maxval() {

    real_t res = array(0);
    for (size_t i = 1; i < array.size(); i++) {
      if (array(i) > res) res = array(i);
    }
    std::cout << "maxval(array) = " << res << std::endl;
    return res;
  }
};

extern "C" {

typedef FortranArray<double> Vector;
typedef UsesFortranArray<Vector> UsesVector;

void print_array_and_maxval(const CFI_cdesc_t *array) {

    // Array is printed in the constructor of FortranArray
    Vector a(array);

    // maxval is printed in constructor of UsesVector
    UsesVector use_f(a);
}

struct CPP_UsesFortranArray {
  void *obj; // Cast of UsesFortranArray<>
};


void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const CFI_cdesc_t *array) {

  // Return if *ptr is not NULL
  if (*ptr != NULL) {
    std::cout << "ptr is not NULL" << std::endl;
    return;
  }

  CPP_UsesFortranArray_t *init_ptr;
  init_ptr = (typeof(init_ptr)) malloc(sizeof(*init_ptr));

  UsesVector *obj = new UsesVector(Vector(array));
  init_ptr->obj = obj;

  *ptr = init_ptr;

}

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr) {

  if (ptr == NULL) return static_cast<double>(1.0/0.0);

  std::cout << "in C_UsesFortranArray_maxval\n";

  UsesVector *obj = static_cast<UsesVector *>((ptr)->obj);
  return obj->maxval();
}

} // extern "C"

Now for the Fortran driver main_foo.f90:

module foo_interface

  use, intrinsic :: iso_c_binding, only: c_double, c_ptr, c_null_ptr
  implicit none

  interface

    ! void print_array_and_maxval(const CFI_cdesc_t *array)
    subroutine print_array_and_maxval(A) &
        bind(c,name="print_array_and_maxval")
      import c_double
      real(c_double), intent(in) :: A(:)
    end subroutine

    ! void C_UsesFortranArray_init(
    !     CPP_UsesFortranArray_t **ptr,
    !     const CFI_cdesc_t *array);
    subroutine C_UsesFortranArray_init(ptr,array) &
        bind(c,name="C_UsesFortranArray_init")
      import c_ptr, c_double
      type(c_ptr), intent(out) :: ptr
      real(c_double), intent(in) :: array(:)
    end subroutine

    ! double C_UsesFortranArray_maxval(CPP_UsesFortranArray_t *ptr);
    real(c_double) function C_UsesFortranArray_maxval(ptr) &
        bind(c,name="C_UsesFortranArray_maxval")
      import c_ptr, c_double
      type(c_ptr), intent(in), value :: ptr
    end function

  end interface

end module

program main_foo

  use, intrinsic :: iso_c_binding
  use foo_interface

  implicit none

  real(c_double) :: A(5)
  type(c_ptr) :: cpp_obj = c_null_ptr

  A = [1,2,3,4,5]

  write(*,*) "--------------------"
  write(*,*) "Calling print_array_and_maxval"
  call print_array_and_maxval(A)
  write(*,*) "--------------------"

  write(*,*) "Before calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)
  call C_UsesFortranArray_init(cpp_obj,A)
  write(*,*) "After calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)

  write(*,*) "maxval in Fortran", maxval(A)


  ! Something goes wrong in this call
  write(*,*) "maxval in C++    ", C_UsesFortranArray_maxval(cpp_obj)

end program

Output:

~/fortran/mwe$ g++ -I./ -Wall foo.cpp -c
~/fortran/mwe$ gfortran foo.o main_foo.f90 -o main_foo -lstdc++
~/fortran/mwe$ ./main_foo 
 --------------------
 Calling print_array_and_maxval
In FortranArray Constructor: 
obj[0] = 1
obj[1] = 2
obj[2] = 3
obj[3] = 4
obj[4] = 5
In UsesFortranArray Constructor
maxval(array) = 5
 --------------------
 Before calling constructor:
   associated(cpp_obj) =  F
In FortranArray Constructor: 
obj[0] = 1
obj[1] = 2
obj[2] = 3
obj[3] = 4
obj[4] = 5
In UsesFortranArray Constructor
maxval(array) = 5
 After calling constructor:
   associated(cpp_obj) =  T
 maxval in Fortran   5.0000000000000000     
in C_UsesFortranArray_maxval

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7f526073ab2a
#1  0x7f5260739d25
#2  0x7f526015103f
#3  0x555d0eab435c
#4  0x555d0eab428a
#5  0x555d0eab40a9
#6  0x555d0eab49b2
#7  0x555d0eab4a1c
#8  0x7f5260133bf6
#9  0x555d0eab3e59
#10  0xffffffffffffffff
Segmentation fault (core dumped)

The segfault appears to originate in foo.cpp in the maxval() function inside of UsesFortranArray when attempting to retrieve the value array(0).

1 Like

I think the problem is coming from the fact that Vector(array) only exists in the scoping unit of C_UsesFortranArray_init. Furthermore, I am not sure the C descriptor *array survives until the call to the wrapped maxval routine.

Yes, I believe both your points are correct. The interface should be:

    real(c_double) function C_UsesFortranArray_maxval(ptr) &
        bind(c,name="C_UsesFortranArray_maxval")
      import c_ptr, c_double
      type(c_ptr), intent(in), value :: ptr
    end function

I will amend the snippet above.

Using assumed-size arrays (instead of assumed-shape) I was able to arrive at a working solution. I did however store a pointer to the Fortran array class, along with the UsesFortranArray object.

Note that a call to a destructor method is needed in both examples, but is missing!

Solution using assumed size arrays

foo.h:

#ifndef FOO_H_
#define FOO_H_

#include "ISO_Fortran_binding.h"

#ifdef __cplusplus
extern "C" {
#endif

struct CPP_UsesFortranArray;
typedef struct CPP_UsesFortranArray CPP_UsesFortranArray_t;

/*void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const CFI_cdesc_t *array);*/

void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const double *array, const int n);

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr);

void print_array_and_maxval(const int n, const double *array);

#ifdef __cplusplus
}
#endif

#endif // FOO_H_

foo.cpp:

#include "foo.h"

#include <iostream>
#include <cmath>

template <typename T>
struct FortranAssumedSizedArray {

  typedef T real_t;

  // A const reference to rank 1 assumed-size Fortran array
  const T *obj;
  const int n;

  // Constructor
  FortranAssumedSizedArray(const T *obj_, const int n_) : obj(obj_), n(n_) {
    std::cout << "In FortranAssumedSizedArray Constructor: " << std::endl;
    for (size_t i = 0; i < this->size(); i++) {
      std::cout << "obj[" << i <<"] = " << this->operator()(i) << std::endl;
    }
  }

  // Returns the i'th element of the vector
  inline T operator()(const size_t i) const {
    return obj[i];
  }

  inline size_t size() const {
    return n;
  }
};


template <typename ArrayType>
class UsesFortranArray {

  const ArrayType &array; // Reference to a Fortran array

  typedef typename ArrayType::real_t real_t;

public:

  // Constructor
  UsesFortranArray(const ArrayType &inputArray) :
    array(inputArray) {
      std::cout << "In UsesFortranArray Constructor" << std::endl;
      this->maxval();
    }

  real_t maxval() {

    real_t res = array(0);
    for (size_t i = 1; i < array.size(); i++) {
      if (array(i) > res) res = array(i);
    }
    std::cout << "maxval(array) = " << res << std::endl;
    return res;
  }
};

extern "C" {

//typedef FortranArray<double> Vector;
typedef FortranAssumedSizedArray<double> Vector;
typedef UsesFortranArray<Vector> UsesVector;

void print_array_and_maxval(const int n, const double *array) {

    // Array is printed in the constructor of FortranArray
    Vector a(array,n);

    // maxval is printed in constructor of UsesVector
    UsesVector use_f(a);
}

struct CPP_UsesFortranArray {
  void *obj; // Cast of UsesFortranArray<>
  void *arr; // Cast of FortranArray<>
};


void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const double *array, const int n) {

  // Return if *ptr is not NULL
  if (*ptr != NULL) {
    std::cout << "ptr is not NULL" << std::endl;
    return;
  }

  CPP_UsesFortranArray_t *init_ptr;
  init_ptr = (typeof(init_ptr)) malloc(sizeof(*init_ptr));

  Vector *vec = new Vector(array, n);
  init_ptr->arr = vec;

  UsesVector *obj = new UsesVector(*vec);
  init_ptr->obj = obj;

  *ptr = init_ptr;

}

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr) {

  if (ptr == NULL) return static_cast<double>(1.0/0.0);

  std::cout << "in C_UsesFortranArray_maxval\n";

  UsesVector *obj = static_cast<UsesVector *>((ptr)->obj);
  return obj->maxval();
}

} // extern "C"

main_foo.f90:

module foo_interface

  use, intrinsic :: iso_c_binding, only: c_int, c_double, c_ptr, c_null_ptr
  implicit none

  interface

    ! void print_array_and_maxval(const CFI_cdesc_t *array)
    ! subroutine print_array_and_maxval(A) &
    !     bind(c,name="print_array_and_maxval")
    !   import c_double
    !   real(c_double), intent(in) :: A(:)
    ! end subroutine
    subroutine print_array_and_maxval(n,A) &
        bind(c,name="print_array_and_maxval")
      import c_int, c_double
      integer(c_int), intent(in), value :: n
      real(c_double), intent(in), target :: A(*)
    end subroutine

    ! void C_UsesFortranArray_init(
    !     CPP_UsesFortranArray_t **ptr,
    !     const CFI_cdesc_t *array);
    ! subroutine C_UsesFortranArray_init(ptr,array) &
    !     bind(c,name="C_UsesFortranArray_init")
    !   import c_ptr, c_double
    !   type(c_ptr), intent(out) :: ptr
    !   real(c_double), intent(in) :: array(:)
    ! end subroutine
    subroutine C_UsesFortranArray_init(ptr,array,n) &
        bind(c,name="C_UsesFortranArray_init")
      import c_ptr, c_double, c_int
      type(c_ptr), intent(out) :: ptr
      real(c_double), intent(in), target :: array(*)
      integer(c_int), intent(in), value :: n
    end subroutine

    ! double C_UsesFortranArray_maxval(CPP_UsesFortranArray_t *ptr);
    real(c_double) function C_UsesFortranArray_maxval(ptr) &
        bind(c,name="C_UsesFortranArray_maxval")
      import c_ptr, c_double
      type(c_ptr), intent(in), value :: ptr
    end function

  end interface

end module

program main_foo

  use, intrinsic :: iso_c_binding
  use foo_interface

  implicit none

  integer, parameter :: n = 5
  real(c_double) :: A(n)
  type(c_ptr) :: cpp_obj = c_null_ptr

  A = [1,2,3,4,5]


  write(*,*) "--------------------"
  write(*,*) "Calling print_array_and_maxval"
  call print_array_and_maxval(n,A)
  write(*,*) "--------------------"



  write(*,*) "Before calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)
  call C_UsesFortranArray_init(cpp_obj,A,n)
  write(*,*) "After calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)

  ! Works till here

  ! Something wrong in this call
  write(*,*) "maxval in Fortran", maxval(A)
  write(*,*) "maxval in C++    ", C_UsesFortranArray_maxval(cpp_obj)

  A(1) = 6.0_c_double
  write(*,*) "new maxval in C++    ", C_UsesFortranArray_maxval(cpp_obj)

end program

Output:

~/fortran/fortran-nanoflann/mwe$ g++ -I./ -Wall foo.cpp -c
~/fortran/fortran-nanoflann/mwe$ gfortran foo.o main_foo.f90 -o main_foo -lstdc++
~/fortran/fortran-nanoflann/mwe$ ./main_foo 
 --------------------
 Calling print_array_and_maxval
In FortranAssumedSizedArray Constructor: 
obj[0] = 1
obj[1] = 2
obj[2] = 3
obj[3] = 4
obj[4] = 5
In UsesFortranArray Constructor
maxval(array) = 5
 --------------------
 Before calling constructor:
   associated(cpp_obj) =  F
In FortranAssumedSizedArray Constructor: 
obj[0] = 1
obj[1] = 2
obj[2] = 3
obj[3] = 4
obj[4] = 5
In UsesFortranArray Constructor
maxval(array) = 5
 After calling constructor:
   associated(cpp_obj) =  T
 maxval in Fortran   5.0000000000000000     
in C_UsesFortranArray_maxval
maxval(array) = 5
 maxval in C++       5.0000000000000000     
in C_UsesFortranArray_maxval
maxval(array) = 6
 new maxval in C++       6.0000000000000000     
1 Like

Hi @ivanpribec, I had a look at the code from your original post using the C descriptor and I think I’ve got it working. I think you are right that the C descriptor does not survive the initial call.

From the interpretation document 18-007r1, section 18.8 Restrictions on lifetimes, paragraph 2:

A C descriptor whose address is a formal parameter that corresponds to a Fortran dummy argument becomes undefined on return from a call to the function from Fortran. If the dummy argument does not have either the TARGET or ASYNCHRONOUS attribute, all C pointers to any part of the object described by the C descriptor become undefined on return from the call, and any further use of them is undefined behavior.

Based on this I changed the FortranArray class to instead store the base_addr and dim components of the C descriptor and added the TARGET attribute to A in the Fortran driver. I also removed the inadvertent reference to a temporary Vector in C_UsesFortranArray_init.

The implementation (see below) works with gfortran-10 and icc-2021.1.2.

Full implementation

foo.h (unchanged)

#ifndef FOO_H_
#define FOO_H_

#include "ISO_Fortran_binding.h"

#ifdef __cplusplus
extern "C" {
#endif

struct CPP_UsesFortranArray;
typedef struct CPP_UsesFortranArray CPP_UsesFortranArray_t;

void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const CFI_cdesc_t *array);

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr);

void print_array_and_maxval(const CFI_cdesc_t *array);

#ifdef __cplusplus
}
#endif

#endif // FOO_H_

foo.cpp

#include "foo.h"

#include <iostream>
#include <cmath>

template <typename T>
struct FortranArray {

  typedef T real_t;

  const void *base_addr;

  const CFI_dim_t *dim;

  // Constructor
  FortranArray(const CFI_cdesc_t *obj_) : base_addr(obj_->base_addr), dim(obj_->dim){
    std::cout << "In FortranArray Constructor: " << std::endl;
    for (size_t i = 0; i < this->size(); i++) {
      std::cout << "obj[" << i <<"] = " << this->operator()(i) << std::endl;
    }
  }

  // Returns the i'th element of the vector
  inline T operator()(const size_t i) const {
    char *elt = (char *) base_addr;
    elt += (i*dim[0].sm);
    return *(T *) elt;
  }

  inline size_t size() const {
    return dim[0].extent;
  }
};

template <typename ArrayType>
class UsesFortranArray {

  const ArrayType &array; // Reference to a Fortran array

  typedef typename ArrayType::real_t real_t;

public:

  // Constructor
  UsesFortranArray(const ArrayType &inputArray) :
    array(inputArray) {
      std::cout << "In UsesFortranArray Constructor" << std::endl;
      this->maxval();
    }

  real_t maxval() {

    real_t res = array(0);
    for (size_t i = 1; i < array.size(); i++) {
      if (array(i) > res) res = array(i);
    }
    std::cout << "maxval(array) = " << res << std::endl;
    return res;
  }
};

extern "C" {

typedef FortranArray<double> Vector;
typedef UsesFortranArray<Vector> UsesVector;

void print_array_and_maxval(const CFI_cdesc_t *array) {

    // Array is printed in the constructor of FortranArray
    Vector a(array);

    // maxval is printed in constructor of UsesVector
    UsesVector use_f(a);
}

struct CPP_UsesFortranArray {
  void *obj; // Cast of UsesFortranArray<>
};


void C_UsesFortranArray_init(
    CPP_UsesFortranArray_t **ptr,
    const CFI_cdesc_t *array) {

  // Return if *ptr is not NULL
  if (*ptr != NULL) {
    std::cout << "ptr is not NULL" << std::endl;
    return;
  }

  CPP_UsesFortranArray_t *init_ptr;
  init_ptr = (typeof(init_ptr)) malloc(sizeof(*init_ptr));

  Vector *vec = new Vector(array);
  UsesVector *obj = new UsesVector(*vec);
  init_ptr->obj = obj;

  *ptr = init_ptr;

}

double C_UsesFortranArray_maxval(const CPP_UsesFortranArray_t *ptr) {

  if (ptr == NULL) return static_cast<double>(1.0/0.0);

  std::cout << "in C_UsesFortranArray_maxval\n";

  UsesVector *obj = static_cast<UsesVector *>((ptr)->obj);
  return obj->maxval();
}

} // extern "C"

main_foo.f90 (just added target attribute)

module foo_interface

  use, intrinsic :: iso_c_binding, only: c_double, c_ptr, c_null_ptr
  implicit none

  interface

    ! void print_array_and_maxval(const CFI_cdesc_t *array)
    subroutine print_array_and_maxval(A) &
        bind(c,name="print_array_and_maxval")
      import c_double
      real(c_double), intent(in), target :: A(:)
    end subroutine

    ! void C_UsesFortranArray_init(
    !     CPP_UsesFortranArray_t **ptr,
    !     const CFI_cdesc_t *array);
    subroutine C_UsesFortranArray_init(ptr,array) &
        bind(c,name="C_UsesFortranArray_init")
      import c_ptr, c_double
      type(c_ptr), intent(out) :: ptr
      real(c_double), intent(in), target :: array(:)
    end subroutine

    ! double C_UsesFortranArray_maxval(CPP_UsesFortranArray_t *ptr);
    real(c_double) function C_UsesFortranArray_maxval(ptr) &
        bind(c,name="C_UsesFortranArray_maxval")
      import c_ptr, c_double
      type(c_ptr), intent(in), value :: ptr
    end function

  end interface

end module

program main_foo

  use, intrinsic :: iso_c_binding
  use foo_interface

  implicit none

  real(c_double), target :: A(5)
  type(c_ptr) :: cpp_obj = c_null_ptr

  A = [1,2,3,4,5]

  write(*,*) "--------------------"
  write(*,*) "Calling print_array_and_maxval"
  call print_array_and_maxval(A)
  write(*,*) "--------------------"

  write(*,*) "Before calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)
  call C_UsesFortranArray_init(cpp_obj,A)
  write(*,*) "After calling constructor:"
  write(*,*) "  associated(cpp_obj) = ", c_associated(cpp_obj)

  write(*,*) "maxval in Fortran", maxval(A)


  ! Something goes wrong in this call
  write(*,*) "maxval in C++    ", C_UsesFortranArray_maxval(cpp_obj)

end program
2 Likes

Thanks Laurence! That makes a lot of sense.

I can confirm that it works also when I pass an array slice. :rocket:

  real(c_double), target :: A(5,2)
  A = reshape([1,2,3,4,5,6,7,8,9,10],[5,2])
  call C_UsesFortranArray_init(cpp_obj,A(:,2))
  print *, C_UsesFortranArray_maxval(cpp_obj) ! prints the value 10

One concern that remains is that the FortranArray wrapper struct, initialized in the line Vector *vec = new Vector(array); lives now only as a reference within UsesFortranArray. I think that using the std::shared_ptr<> as in:

  auto vec = std::make_shared<Vector>(array);
  UsesVector *obj = new UsesVector(*vec);
  init_ptr->obj = obj;

will create a smart pointer, which will be deallocated once no more objects contain references to it.

(I don’t know if this also works for the pointer to UsesFortranArray which lives only the Fortran side.)

2 Likes

I found a short explanation of the inconsistency in a source code comment:

//   In C++ bool is a keyword while in C99 bool is a macro defined
//   in stdbool.h. It is possible for the two to be inconsistent.
//   For example, neither the C99 nor the C++11 standard force a byte
//   size on the bool type, so the macro defined in stdbool.h could
//   be inconsistent with the bool keyword in C++. Thus, the use
//   of stdbool.h is avoided and unsigned char is used instead.

It might be best to avoid the C bool in mixed-language programming.

2 Likes

More precisely, in C (>=99) the stdbool.h contains:

#define bool    _Bool
#define true    1
#define false   0

That was defined for compatibility with old programs.

Therefore bool is a macro, but _Bool is the true type. And the C18 standard says:

An object declared as type _Bool is large enough to store the values 0 and 1.

When any scalar value is converted to _Bool , the result is 0 if the value compares equal to 0; otherwise, the result is 1.

Note also that true and false are only defined in stdbool.h. _Bool is 0 or 1.

The standard also says:

While the number of bits in a _Bool object is at least CHAR_BIT, the width (number of sign and value bits) of a _Bool may be just 1 bit.

That C++ standard draft (2020-04-02) says:

Type bool is a distinct type that has the same object representation, value representation, and alignment requirements as an implementation-defined unsigned integer type. The values of type bool are true and false. [Note: There are no signed,unsigned,short, or long bool types or values.— end note]

Therefore, bool is a fundamental type in C++ with two values true and false.

In C, bool is a macro based on the _Bool fundamental type which has two values, 0 and 1. And true and false are just two macros for 1 and 0.

And the Fortran standard says:

For C_BOOL, the internal representation of .TRUE._C_BOOL and .FALSE._C_BOOL shall be the same as those of the C values (_Bool)1 and (_Bool)0 respectively.

So Fortran does not know bool. He only knows _Bool.