Issues interfacing between C++ and Fortran

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