Consider the following Fortran code, where the C-interoperable subroutine runFoo4C(...) bind(C, name="runFoo")
in module Foo_mod
takes a C-callback function pointer getLogFuncFromC()
as an argument,
module CallbackInterface_mod
abstract interface
function getLogFunc4C_proc(ndim,Point) result(logFunc) ! bind(C)
use, intrinsic :: iso_c_binding, only : c_int32_t, c_double, c_int
integer(c_int32_t), intent(in) :: ndim
real(c_double), intent(in) :: Point(ndim)
real(c_double) :: logFunc
end function getLogFunc4C_proc
end interface
end module CallbackInterface_mod
!***********************************************************************************************************************************
!***********************************************************************************************************************************
module Foo_mod
interface
module subroutine runFoo4C(ndim, getLogFuncFromC, inputString, inputStringLen) bind(C, name="runFoo")
use, intrinsic :: iso_c_binding, only: c_int32_t, c_char, c_funptr, c_f_procpointer, c_size_t
use CallbackInterface_mod, only: getLogFunc4C_proc
implicit none
integer(c_int32_t) , intent(in) :: ndim
character(len=1, kind=c_char), dimension(*), intent(in) :: inputString
integer(c_size_t) , intent(in) :: inputStringLen
type(c_funptr), intent(in), value :: getLogFuncFromC
end subroutine runFoo4C
end interface
contains
subroutine runFoo(ndim, getLogFunc, string)
!use CallbackInterface_mod, only: getLogFunc_proc
use CallbackInterface_mod, only: getLogFunc4C_proc
use, intrinsic :: iso_fortran_env, only: RK => real64
implicit none
integer :: ndim
procedure(getLogFunc4C_proc) :: getLogFunc
character(*), intent(in) :: string
real(RK) :: Point(ndim)
character(:), allocatable :: mystring
Point = [1._RK,1._RK]
write(*,*) "Hi again, this is a call from inside runFoo!"
write(*,*) "getLogFunc(2,[1,1]) = ", getLogFunc(ndim,Point)
write(*,*) "string = ", string
end subroutine
end module Foo_mod
!***********************************************************************************************************************************
!***********************************************************************************************************************************
submodule (Foo_mod) Foo_smod
contains
module subroutine runFoo4C(ndim, getLogFuncFromC, InputString, inputStringLen) bind(C, name="runFoo")
use, intrinsic :: iso_c_binding, only: c_double, c_int32_t, c_char, c_funptr, c_f_procpointer, c_size_t
use CallbackInterface_mod, only: getLogFunc4C_proc
implicit none
integer(c_int32_t) , intent(in) :: ndim
character(len=1, kind=c_char), dimension(*), intent(in) :: InputString
integer(c_size_t) , intent(in) :: inputStringLen
type(c_funptr), intent(in), value :: getLogFuncFromC
procedure(getLogFunc4C_proc), pointer :: getLogFunc
real(c_double) :: Point(ndim)
character(:), allocatable :: inputString4tran
integer :: i
write(*,*) "InputString: ", InputString(1:inputStringLen)
allocate( character(len=inputStringLen) :: inputString4tran )
do i=1,inputStringLen
inputString4tran(i:i) = InputString(i)
end do
write(*,*) "inputString4tran: ", inputString4tran
! associate the input C procedure pointer to a Fortran procedure pointer
call c_f_procpointer(cptr=getLogFuncFromC, fptr=getLogFunc)
Point = [1._c_double, 1._c_double]
write(*,*) "Here we go: "
write(*,*) "getLogFunc(ndim=2, [1._c_double, 1._c_double]): ", getLogFunc( ndim, Point )
call runFoo(ndim, getLogFunc, inputString4tran)
end subroutine runFoo4C
end submodule Foo_smod
The abstract Fortran interface of this callback function, is given by getLogFunc4C_proc()
in module CallbackInterface_mod
in the above code. Now the question:
Does this abstract interface require a bind(c)
attribute to comply with the fortran standard? My own naive guess is that it does not need the bind(c)
as it is not going to be called with the global identifier of the function in the interface, but the abstract interface simply determines the interface of the C callback function, a pointer to which is passed to Fortran to be called later from inside Fortran.
Indeed, commenting out this bind(c)
attribute in the abstract interface does not lead to any compilation or runtime error using ifort (18.0.2 Windows compiler).
If it is not needed, then how about variable declarations in this abstract interface? Do they need to be declared by C-conforming kinds from the iso_c_binding
intrinsic module?
The presence (or absence) of BIND(C) in the abstract interface changes the characteristics of the procedure pointer, but does so in a way that this program doesn't reveal. Because you do the call to getLogFunc through a pointer you converted from a C_FUNPTR, you prevent the compiler from noticing the mismatch should BIND(C) be omitted in the abstract interface. For example, should the procedure have a character(*) argument, lots of bad things would happen for a mismatch.
BIND(C), by itself, is fine in an abstract interface, as long as you don't also say NAME=. Since it changes how the procedure is called, you must specify it if the called procedure is interoperable.
Regarding "If it is not needed, then how about variable declarations in this abstract interface? Do they need to be declared by C-conforming kinds from the iso_c_binding intrinsic module?", you make the common error of conflating definitions in intrinsic module ISO_C_BINDING with being interoperable. The kind constants in that module are just numbers, there's nothing magical about them. You are required to have the actual and dummy arguments match in type, kind and rank (with some exceptions.)