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?