C-interoperable Fortran routine with explicit interface

I trying to learn how to write C-interoperable Fortran procedures. I guess, I got the gist of it for normal type arguments, but I am somewhat lost for procedure arguments.

Let us suppose the following procedure with an explicit interface:

real(dp) function averagefnc(fnc, a, b) result(res)
  !! Average of function with explicit interface
  interface 
     function fnc(x)
        import dp
        real(dp), intent(in) :: x
        real(dp) :: fnc
     end function
  end interface
  real(dp), intent(in) :: a, b
  res = (fnc(a) + fnc(b))/2
end function

Could the C-interoperable Fortran procedure look like so?

real(c_double) function averagefnc_c(fnc, a, b) result(res) bind(c)
  interface
     function fnc(x) bind(c)
        import c_double
        real(c_double), intent(in) :: x
        real(c_double) :: fnc
     end function   
  end interface
  real(c_double), intent(in) :: a, b
  res = averagefnc(fnc, a, b) ! something is still missing here, I imagine
end function

Or is it necessary to transform the explicit interface into an abstract interface and do as described here: Working with C Pointers (The GNU Fortran Compiler)?

Any hints on documentation and/or an open source project that makes use of such features are also very welcome.

Hi @HugoMVale. Perhaps I misunderstand what you’re doing but this seems slightly over-complicated to me.

All of the “kernels” with public interfaces in this open-source repo are bound to C. Each related set of kernels lives in a module, so the interface is generated from the function definition. Arguments to kernel routines are all C-compatible variables (e.g arrays have to be explicit size), so adding C binding is easy, e.g.

module mo_fluxes_broadband_kernels
contains
subroutine net_broadband_full(ncol, nlev, ngpt, spectral_flux_dn, spectral_flux_up, broadband_flux_net) &
    bind(C, name="rte_net_broadband_full")
    integer,                               intent(in ) :: ncol, nlev, ngpt
      !! Array sizes
    real(wp), dimension(ncol, nlev, ngpt), intent(in ) :: spectral_flux_dn, spectral_flux_up
      !! Spectrally-resolved flux up and down
    real(wp), dimension(ncol, nlev),       intent(out) :: broadband_flux_net
   ...
  end subroutine

Mapping to your code:

module average
  use, intrinsic :: iso_c_binding
  implicit none
  public :: averagefnc_c
contains 
  function averagefnc_c(fnc, a, b) result(res) bind(c, name = "averagefnc_c")
    real(c_double), intent(in) :: x
    real(c_double), intent(in) :: a, b
    real(c_double) :: res
    real(c_double) :: fnc ! Declared as a scalar - is that what's meant?
    res = averagefnc(fnc, a, b) ! something is still missing here, I imagine
  end function

Did that address the question?

Thanks. However, I fell there is a misunderstanding. fnc is not a number, it’s a function.

This Fortran-lang Project MinPack has c func binding,It can be a reference.

and this way also works

module func
   use iso_fortran_env,only:dp=>real64
   implicit none
   abstract interface 
      function fnc(x)bind(c)
         import dp
         real(dp), value :: x
         real(dp) :: fnc
      end function
   end interface
contains
   real(dp) function averagefnc(fc, a, b) result(res)bind(c,name="averagefnc_api")
      real(dp), value :: a, b
      procedure(fnc)::fc
      res = (fc(a) + fc(b))/2
   end function
end module func
#include <stdio.h>
#include <stdlib.h>
#include <math.h>
double averagefnc_api(double(*func)(double),double ,double);
double func(double x){
   return sin(x);
}

int main(){
   printf("%lf\n",averagefnc_api(func,1.0,2.0));
}

Thanks for pointing me to the minpack project. That is indeed a good source of inspiration. :slight_smile:

The answer you provided was not quite yet what I was looking for, but it made me realize what the problem was.

I want to keep the function averagefnc (this is just a toy procedure) as a normal Fortran function. It’s C-counterpart averagefnc_c is meant as a wrapper to allow one to invoke averagefnc from C. Since fnc will ultimately be called inside averagefnc it must, like normal Fortran functions, have the argument(s) passed by reference not by value.

So, the issue was not on the Fortran side, but on the C-side. As shown below it works fine

module fmodule
   !! A module with various toy functions and subroutines to learn how to invoke fortran code
   !! from python.
   use, intrinsic :: iso_fortran_env, only: real32, real64
   implicit none
   private
   public :: intsum, real4sum, real8sum, vector4sum, matrix8sum, saxpy, matrixtimesvector
   public :: averagefnc

   integer, parameter :: sp = real32
   integer, parameter :: dp = real64

contains
  
  ! ...

   real(dp) function averagefnc(fnc, a, b) result(res)
      !! Average of function with explicit interface
      interface
         function fnc(x)
            import dp
            real(dp), intent(in) :: x
            real(dp) :: fnc
         end function
      end interface
      real(dp), intent(in) :: a, b
      res = (fnc(a) + fnc(b))/2
   end function

end module fmodule
module fmodule_bindings
   use fmodule
   use iso_c_binding, only: c_float, c_double, c_int
   implicit none

   abstract interface 
      function fx_c(x) bind(c)
         import c_double
         real(c_double), intent(in) :: x
         real(c_double) :: fx_c
      end function
   end interface

contains

   ! ...

   real(c_double) function averagefnc_abstract_c(fnc, a, b) result(res) bind(c, name='averagefnc_abstract')
      procedure(fx_c) :: fnc
      real(c_double), intent(in) :: a, b
      res = averagefnc(fnc, a, b)
   end function

   real(c_double) function averagefnc_explicit_c(fnc, a, b) result(res) bind(c, name='averagefnc_explicit')
      interface 
         function fnc(x) bind(c)
            import c_double
            real(c_double), intent(in) :: x
            real(c_double) :: fnc
         end function
      end interface
      real(c_double), intent(in) :: a, b
      res = averagefnc(fnc, a, b)
   end function

end module fmodule_bindings
#include <stdio.h>
#include <stdlib.h>
#include <math.h>

double averagefnc_abstract(double(*func)(double*), double*, double*);
double averagefnc_explicit(double(*func)(double*), double*, double*);

double func(double* x){
   return *x;
}

int main(){
   double a = 1.;
   double b = 2.;
   printf("%lf\n", averagefnc_abstract(func, &a, &b));
   a = 3.;
   b = 4.;
   printf("%lf\n", averagefnc_explicit(func, &a, &b));
}