Passing Fortran (abstract interface) procedure to C

Greetings,

I’d like to register a Fortran callback procedure to be called from C. The following example works fine:

module x
    use, intrinsic :: iso_c_binding
    implicit none
contains
    subroutine handler(a) bind(c)
        real(c_float), intent(in), value :: a
        print *, a
    end subroutine handler
end module x

program main
    use, intrinsic :: iso_c_binding
    use :: x
    implicit none

    interface
        subroutine c_register_callback(p) bind(c, name='register_callback')
            import :: c_funptr
            implicit none
            type(c_funptr), intent(in), value :: p
        end subroutine c_register_callback
    end interface

    call c_register_callback(c_funloc(handler))
end program main

The expected procedure is not enforced in this example, as any function or subroutine could possibly be passed to the C register routine. I thought of adding an abstract interface:

program main
    use, intrinsic :: iso_c_binding
    use :: x
    implicit none

    interface
        subroutine c_register_callback(p) bind(c, name='register_callback')
            import :: c_funptr
            implicit none
            type(c_funptr), intent(in), value :: p
        end subroutine c_register_callback
    end interface

    abstract interface
        subroutine c_handler_callback(a) bind(c)
            import :: c_float
            implicit none
            real(c_float), intent(in), value :: a
        end subroutine c_handler_callback
    end interface

    procedure(c_handler_callback), pointer :: funptr

    funptr => handler
    call register(funptr)
contains
    subroutine register(funptr)
        procedure(c_sub_callback), pointer :: funptr
        call c_register_callback(c_funloc(funptr))
    end subroutine register
end program main

But this leads to a SIGSEGV whenever the callback procedure is called from C:

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

Backtrace for this error:
#0  0x800a20229 in ???
#1  0x800a1f3a6 in ???
#2  0x800867dff in ???
#3  0x8008673ce in ???
#4  0x7ffffffff192 in ???
Memory faul

Did the pointer passed by c_funloc() go out of scope? Is this approach even allowed?

1 Like

You don’t need the extra indirection with the POINTER attribute and the referencing with C_FUNLOC.

Mostly with other readers in mind who may be starting new with C <-> Fortran interoperability, here’s a simple example to try:

  • Fortran “library”:
module m
   use, intrinsic :: iso_c_binding, only : c_int
   abstract interface
      function ICallback() result(r) bind(C)
         import :: c_int
         ! Function result
         integer(c_int) :: r
      end function
   end interface
   procedure(ICallback), pointer :: C_Callback => null()
contains
   subroutine Fsub() bind(C, name="Fsub")
      print *, "C callback returns: ", C_Callback()
   end subroutine
   subroutine SetCallback( Callback ) bind(C, name="SetCallback")
      ! Argument list
      procedure(ICallback) :: Callback
      ! checks elided
      C_Callback => Callback
   end subroutine
end module
  • C caller that registers callback and consumes the Fortran library
// Function pointer prototype for callback
typedef int (*ICallback)();
// Fortran library functions
extern void SetCallback(ICallback);
extern void Fsub();
// Caller functions
int my_callback();

int main ()
{
   SetCallback( (ICallback)my_callback ); //<-- register the callback
   Fsub();                                //<-- consume the library
   return 0;
}

int my_callback() {
  return 42;
}
  • program behavior:
C:\temp>gfortran -c c.c

C:\temp>gfortran -c f.f90

C:\temp>gfortran c.o f.o -o c.exe

C:\temp>c.exe
 C callback returns:           42

1 Like

Your example shows a different use case, I guess. I donʼt have control over the C side, and therefore have to pass a c_funptr to the register interface routine.

No, you don’t. The “library” code on the Fortran side can still be as I showed upthread.

If you “don’t have control over the C side,” the C callers will have to make do with no blade guard there - nothing new though!! That’s why how it was for quite a while, before Fortran standard introduced interoperability facilities.

You are correct, the problem is the pointer attribute of the funptr dummy argument. This way, it works:

    subroutine register(funptr)
        procedure(c_sub_callback) :: funptr
        call c_register_callback(c_funloc(funptr))
    end subroutine register