bind(C) philosophy: pointer-by-value or type-by-reference?

Digging more and more into Fortran-C binding stuff I constantly need to deal with the question whether I should interface fortran to a C pointer or to keep types as much as possible in the interface.

For example, assume I want some Fortran code to write data to a C array:

void copy_array() {

   // Allocate memory
   double* c_array = new double[10];

   // Fortran->C++ Copy data
   fortran_wrapper(c_array,10);
    
   // do other stuff
}

Now, there are two ways: 1) by passing an opaque pointer to Fortran, then assigning its type internally:

subroutine fortran_wrapper(array, nelem) bind(C,name="fortran_wrapper")
   type(c_ptr), intent(in), value :: array
   integer(c_int), intent(in), value :: nelem
   real(c_double), pointer :: the_data(:)
   integer :: j
   
   call c_f_pointer(array, the_data, [nelem])

   ! Copy data
   the_data = [(j,j=1,nelem)]

end subroutine fortran_wrapper

The other is to assume the data type in the interface, and pass it via reference

subroutine fortran_wrapper2(array, nelem) bind(C,name="fortran_wrapper2")
   real(c_double), intent(inout) :: array(*)
   integer(c_int), intent(in), value :: nelem
   integer :: j
   
   ! Copy data
   array = [(j,j=1,nelem)]

end subroutine fortran_wrapper2

Now, besides this is an obviously elementary case, is there any hidden caveats I should be aware of? Like, something that may impact the C ABI in case the Fortran stuff becomes a library? Or, should I prefer either one over the other for non-trivial reasons?

If you can work with a processor conformant with the current standard, my suggestion will be to

  • have your Fortran “APIs” be as per your Fortran style, for example with assumed-shape dummy arguments that are >= rank-1
  • then employ ISO_Fortran_binding.h-based facility in the C wrapper (“extern” C) to your C++ code to interoperate with such Fortran APIs,
  • and strive for type and kind safety as much as viable i.e., if supported types with some API are integer and real of some kinds, be specific as to what type and kind in the Fortran subprograms.
subroutine fortran_api_x( arr_real ) bind(C, name="fortran_api_x")
   real(c_double), intent(inout) :: arr_real(:)
..
1 Like

The rule of thumb I am following is “port variables as C is supposed to do”. A C function has an argument int i? Port it using integer(kind=c_int), value :: i. A C function returns an argument float foo[10]? Port it as real(kind=c_float), dimension(10), intent(out) :: foo. It all depends on how the C function treats its arguments. There is no need to go for your second solution, and your first solution is not really needed either, except for C strings, which are essentially pointers - and in that case the Fortran function should actually do more than what you do.

1 Like

Based on my experience with writing Fortran C-interop interfaces, my advice is to spend a little time writing small programs that test the specific data exchange you need to perform in your main code and stick with What Works. Try to mimic the C interface as much as possible. If C defines an argument as float a, pass the array to from Fortran as Real :: a(*), etc. The tricky things are when to pass by value and trying to unravel multiple indirection pointers ( float ***a) particularly if they are imbedded in a C structure.

TL;DR: Fortran code can be kept simple and clean and type and kind safe and without the use of POINTERs etc. by moving all the complexity to the C wrapper side.

As I suggested upthread, if one can use a conformant compiler with current standard, the long, oft painful experiences over decades of interoperating with a C processor and legacy FORTRAN style assumed-size dummy arguments - first with nonstandard means such as compiler-specific directive-enhanced or preprocessors and later with Fortran 2003 - can be put to rest. And follow Fortran style data attributes.

OP might be more into C++ than C and most C compilers are now C++ compilers supporting C.

Thus for a Fortran subprogram to write data into an array (say rank-1) of c_double type and kind, one can consider assumed-shape arguments:

module m
   use, intrinsic :: iso_c_binding, only : c_double
contains
   subroutine WriteData( a ) bind(C, name="WriteData")
      real(c_double), intent(inout) :: a(:)  !<-- type specific argument with array descriptor info to boot
      a = [( real(i, kind(a)), integer :: i = 1, size(a) )]
   end subroutine 
end module 

The caller may be C++ employing std::vector container:

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

extern "C" {
   // Prototype for the function that is defined on the Fortran side.
   void WriteData(CFI_cdesc_t*);
}

int main()
{
   // Use of CFI descriptor macro for rank-1 object
   CFI_CDESC_T(1) a;
   std::vector<double> v(3);

   CFI_index_t ext[1];

   ext[0] = (CFI_index_t)v.size();
   int irc = CFI_establish((CFI_cdesc_t*)&a, v.data(), CFI_attribute_other, CFI_type_double, sizeof(double),
      (CFI_rank_t)1, ext);
   if (irc == CFI_SUCCESS) {
      WriteData((CFI_cdesc_t*)&a);
   }
   for (size_t i=0; i < v.size(); i++) {
       cout << v[i] << ' ';
   }

   return 0;
}
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.6.0 Build 20220226_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.


C:\temp>cl /c /EHsc /W3 c++.cpp
Microsoft (R) C/C++ Optimizing Compiler Version 19.30.30706 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.30.30706.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c++.exe
1 2 3

This is awesome! I’m not very used to the ISO_Fortran_binding.h but it looks interesting: in other words, the CFI descriptor types expose to C the representations of the array data structure being used by the Fortran compiler. So I guess it would be possible to wrap that into a C++ class and make a sort of “Fortran array” in C++?

@Pap @rwmsu Thank you, I agree: this is the way I work when exposing C libraries to Fortran. Exposing Fortran to C/C++ instead requires decisions especially with routines that return array data - who allocates that memory (C or Fortran?) and hence, should Fortran work on the pointer directly vs. on array data. Actually, @FortranFan’s answer makes me think that, wrapping Fortran arrays into a C struct via ISO_Fortran_binding.h, everything would be much easier! But, I don’t think that is going to work if Fortran code is packed into a library and connected to another application via that (e.g.: MSVC application that links to Fortran .dll)

Technically there is not an issue with packaging Fortran code in a library/DLL including when enhanced interoperability with C features is in effect. On Windows using MSVC and IFORT, you should find it work alright.

The problem is more with robust Fortran processor support for the current Fortran standard. Issues here make users wary and stick with prior ways and those working on the implementation see slow to no adoption and then think new features are of no use. It’s a bad feedback loop.

If you have to deal with C arrays interoperability, and you don’t know in advance the size of the array, you definitely need to work with pointers. This is always the case with C strings as well (with the added “trouble” you need to deal with C’s \0 signaling the end of the string).
I always go the Fortran way, binding some C libraries if necessary - not the other way around. So I can’t comment on ISO_Fortran_binding.h because I never really needed it.

It’s certainly possible. Previously, I’ve proposed a Fortran/C++ compatibility library (Fortran/C++ compatibility library · Issue #325 · fortran-lang/stdlib · GitHub) but the issue didn’t get much attention. Presumably there is low community interest.

At least for vectors of intrinsic kinds, it’s fairly simple to have iterator access when working from C++. This also allows you to use STL routines which rely on iterator access.

For tensors (arrays of rank 2 and higher) the situation is more precarious. If you consider how many C++ matrix libraries are out there: Eigen, Armadillo, Blaze, Boost UBLAS,… , you may infer there are (too) many different ways to achieve the same thing with various trade-offs with respect to expressivity and performance. The amount of effort which has gone into these libraries is much higher than what a single programmer could meaningfully spend without backing from an institution or unless persistent enough to develop them over a long time period.

I would note that Eigen and also Armadillo have facilities to interface with a raw C buffer. This can be used also for Fortran arrays. In both cases of C/Fortran calling you need to be careful with who allocates the memory. Here’s an example of using Eigen from Fortran:

/* multiply_by_two.cc */

#include<Eigen/Dense>

#ifdef __cplusplus
extern "C" {
#endif

// Multiplies a C or Fortran array by the scalar 2
//
//  Inputs: 
//     nx, ny - dimensions of the array
//     a - pointer to a float array
//
void multiply_by_two(int nx, int ny, float* a) {

	Eigen::Map<Eigen::Matrix<float,Eigen::Dynamic,Eigen::Dynamic>> a_m(a,nx,ny);
	a_m *= 2;	

}

#ifdef __cplusplus
}
#endif
! call_eigen.f90
!
program call_eigen

  use iso_c_binding, only: c_float, c_int
  implicit none

  interface
    subroutine multiply_by_two(nx,ny,a) bind(c,name="multiply_by_two")
      import c_float, c_int
      integer(c_int), intent(in), value :: nx, ny
      real(c_float), intent(inout) :: a(nx, ny)
    end subroutine
  end interface

  real(c_float) :: a(3,2)

  a = reshape([real(c_float) :: 1, 2, 3, 4, 5, 6], [3, 2])

  call multiply_by_two(3,2,a)

  print *, a

end program
$ g++ -c multiply_by_two.cc -I /usr/include/eigen3/
$ gfortran call_eigen.f90 multiply_by_two.o -lstdc++
$ ./a.out
   2.00000000       4.00000000       6.00000000       8.00000000       10.0000000       12.0000000    

If interested I also have an example of defining a sparse matrix in CSR format in Fortran, and then using one of Eigen’s iterative solvers to solve for a given RHS.

With the enhanced interoperability features, the Fortran interface could be


    subroutine multiply_by_two(a) bind(c,name="multiply_by_two")
      import c_float
      real(c_float), intent(inout), contiguous :: a(:,:)
    end subroutine

and on the C++ side:

void multiply_by_two(CFI_cdesc_t* a) {

    const void * a_ptr = a->base_addr;
    const CFI_index_t nx = a->dim[0].extent;
    const CFI_index_t ny = a->dim[1].extent;

	Eigen::Map<Eigen::Matrix<float,Eigen::Dynamic,Eigen::Dynamic>> a_m(a,nx,ny);
	a_m *= 2;	

}

Ideally, you would write a small helper template function, which would return the Eigen::Map instance, something like:

auto a_m = asEigenMat<float>(a); // returns Eigen::Map instance
1 Like

Thank you, that’s a neat example - it’s nice to see there’s someone else out there interested in extending Fortran’s scope outside of the Fortran world.
Before this discussion, I didn’t know the C Fortran interface would expose array pointers such as their dimensions, bounds etcetera. That’s exactly what I was thinking when I suggested a bind(cpp) option would be very useful for the numerical computing world (imagine “native” C++ headers for the Fortran arrays, how useful would that be)…

And like you and someone else have mentioned, it may now be too late for this, too many options are already available to C++ users to have them instead to consider Fortran as one realistic alternative.

Well it’s quite new - Fortran 2018. There are not many easily findable examples available. I have only ever seen examples by @FortranFan. I believe it is used in some recent versions of MPI libraries.

You may be aware of recent efforts on linear algebra standardization in C++. This includes the introduction of the mdspan (multi-dimensional span) class in C++, along with a multiple-parameter operator[] for simple array access. This will elevate the “array” experience in C++ bringing it almost on par to Fortran. You can already test mdspan via the Compiler Explorer.

I sometimes see Fortran users who loathe C++, but once you get to know it better, it’s actually very nice to work with. I can certainly understand what Bjarne Stroustrup meant with “Within C++, there is a much smaller and cleaner language struggling to get out”. A very skilled colleague of mine put it this way:

C++ is really complex. But withdrawing to the subset of non-inheritance and value semantics, and using the STL, C++ is like Python. But that simplicity comes at a price. One needs to be disciplined. And you don’t have the freedom anymore, C++ otherwise offers. In a sense, you reduce complexity intentionally by self-restriction.

One of the things that Fortran programmers tend to miss about C++ is just the sheer size of its community. If you take a look through some the CppCon recordings, they are producing excellent material, lots of which is also highly relevant for modern Fortran programming. I’ve found that many of the lessons in Effective C++ by Scott Meyers also carry over to Fortran with some language-specific tweaks.

3 Likes

I have posted more examples at the Intel Fortran forum over the years beginning around 2015 which was about when IFORT included supported for Fortran 2015 that later got delayed to Fortran 2018 standard revision.

The standard document provides all the details on enhanced interoperability with C including ISO_Fortran_binding.h. And MFE by Metcalf et al. explains them, so I have always presumed a few minimal working examples like the one upthread would be adequate for those few users who like to have go-by’s whereas most of the rest will get going on their own.

Somehow the awareness and adoption of enhanced interoperability with C in Fortran appears on the slower side. Some outstanding issues with gfortran implementation until GCC 12.0 might also have played a role and deterred users also from using the features?

1 Like