Reputation: 357
I found an instructive example in : https://numpy.org/devdocs/f2py/python-usage.html#call-back-arguments. Here the fortran routine:
C FILE: CALLBACK.F
SUBROUTINE FOO(FUN,R)
EXTERNAL FUN
INTEGER I
REAL*8 R, FUN
Cf2py intent(out) r
R = 0D0
DO I=-5,5
R = R + FUN(I)
ENDDO
END
C END OF FILE CALLBACK.F
This can be compiled with the comand f2py -c -m callback callback.f and called with the python code:
import callback
print(callback.foo.__doc__)
def f(i):
return i * i
print(callback.foo(f))
Everything works fine. Now, I would like to repeat the test using ctypes. I can compile easily the fortran source with: gfortran -shared callback.f -o callback.dll and I can load the library with:
import ctypes as ct
import numpy as np
# import the dll
fortlib = ct.CDLL('callback.dll')
Questions:
Thanks in advance. Gianmarco
Platform: Anaconda python 3.7.6, Mingw-64 on Windows 10
Upvotes: 2
Views: 516
Reputation: 1835
Good programming style dictates us to never use single-character variable names. A modern Fortran-2008 implementation of your Fortran subroutine would be something similar to the following:
module foo_mod
use iso_c_binding, only: RK => c_double, IK => c_int32_t
implicit none
abstract interface
function getFunVal_proc(inputInteger) result(funVal) bind(C)
import :: RK, IK
implicit none
integer(IK), intent(in), value :: inputInteger
real(RK) :: funVal
end function getFunVal_proc
end interface
contains
subroutine getFoo(getFunValFromC,outputReal) bind(C,name="getFoo")
!DEC$ ATTRIBUTES DLLEXPORT :: getFoo
use, intrinsic :: iso_c_binding, only: c_funptr, c_f_procpointer
implicit none
type(c_funptr), intent(in), value :: getFunValFromC
procedure(getFunVal_proc), pointer :: getFunVal
real(RK), intent(out) :: outputReal
integer(IK) :: indx
! associate the input C procedure pointer to a Fortran procedure pointer
call c_f_procpointer(cptr=getFunValFromC, fptr=getFunVal)
outputReal = 0._RK
do indx = -5,5
write(*,"(*(g0,:,' '))") "value of indx from inside Fortran: ", indx
outputReal = outputReal + getFunVal(indx)
end do
write(*,"(*(g0,:,' '))") "value of outputReal from inside Fortran: ", outputReal
! nullify the Fortran pointer
nullify(getFunVal)
end subroutine getFoo
end module foo_mod
This looks rather verbose, but it is far better than F77. We live in the 21 century, after all. Then you would compile this Fortran code via Intel ifort, for example, like,
ifort /dll /threads /libs:static foo_mod.f90 /exe:foo.dll
Then, you would call getFoo()
from the generated DLL foo.dll
like in the following Python script,
import ctypes as ct
import numpy as np
# This is the Python callback function to be passed to Fortran
def getSquare(inputInteger):
print("value of indx received by getSquare() inside Python: ",inputInteger)
return np.double(inputInteger**2)
# define ctypes wrapper function, with the proper result and argument types
getFunVal_proc = ct.CFUNCTYPE( ct.c_double # callback (python) function result
, ct.c_int32 # callback (python) function input integer argument
)
getSquare_pntr = getFunVal_proc(getSquare)
libpath = "foo.dll"
try:
# open DLL
foolib = ct.CDLL(libpath)
except Exception as e:
import logging
logger = logging.Logger("catch_all")
logger.error(e, exc_info=True)
# define getFoo's interface from Fortran dll
foolib.getFoo.restype = None # return type of the Fortran subroutine/function
foolib.getFoo.argtypes = [ getFunVal_proc # procedure
, ct.POINTER(ct.c_double) # real64 return value
, ]
outputReal = ct.c_double(0.)
foolib.getFoo ( getSquare_pntr
, ct.byref(outputReal)
)
print("value of outputReal received in Python: ", np.double(outputReal))
Running this script would yield something like the following,
In [1]: run main.py
value of indx from inside Fortran: -5
value of indx received by getSquare() inside Python: -5
value of indx from inside Fortran: -4
value of indx received by getSquare() inside Python: -4
value of indx from inside Fortran: -3
value of indx received by getSquare() inside Python: -3
value of indx from inside Fortran: -2
value of indx received by getSquare() inside Python: -2
value of indx from inside Fortran: -1
value of indx received by getSquare() inside Python: -1
value of indx from inside Fortran: 0
value of indx received by getSquare() inside Python: 0
value of indx from inside Fortran: 1
value of indx received by getSquare() inside Python: 1
value of indx from inside Fortran: 2
value of indx received by getSquare() inside Python: 2
value of indx from inside Fortran: 3
value of indx received by getSquare() inside Python: 3
value of indx from inside Fortran: 4
value of indx received by getSquare() inside Python: 4
value of indx from inside Fortran: 5
value of indx received by getSquare() inside Python: 5
value of outputReal from inside Fortran: 110.0000000000000
value of outputReal received in Python: 110.0
The above Python script might again look rather verbose compared to your F2PY code. But it is far more professional, modern, and standard-compliant, both with Python and Fortran standards than your implementation.
footnote: Intel ifort is available free of charge to all students, teachers, and open-source developers on Windows, Linux, and Mac platforms. This does not mean that gfortran is not good. But in my opinion, using gcc on Windows OS is in general no better than a never-ending nightmare (I have no affiliations with Intel, just a user).
Upvotes: 3