python-fortran集成:f2py和ctypes之间的回调比较



我在中找到了一个有启发性的例子:https://numpy.org/devdocs/f2py/python-usage.html#call-支持论点。这里是fortran例程:

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

这可以用comandf2py-c-m回调回调.f编译,并用python代码调用:

import callback
print(callback.foo.__doc__)
def f(i):
return i * i
print(callback.foo(f))

一切都很好。现在,我想用ctypes重复这个测试。我可以用:gfortran-shared callback.f-o callback.dll轻松编译fortran源代码,并且我可以用加载库

import ctypes as ct
import numpy as np
# import the dll
fortlib = ct.CDLL('callback.dll')

问题:

  • 如何在dll中调用像我这样来自ctypes的foo函数用f2py编译的代码怎么样
  • 我如何将两者连接起来是否需要变量(指向函数的指针和指向实数的指针(

提前感谢。Gianmarco

平台:Anaconda python 3.7.6,Windows 10上的Mingw-64

良好的编程风格要求我们永远不要使用单字符变量名。Fortran子程序的现代Fortran-2008实现类似于以下内容:

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

这看起来相当冗长,但它比F77要好得多。毕竟,我们生活在21世纪。然后,您可以通过英特尔ifort编译此Fortran代码,例如,

ifort /dll /threads /libs:static foo_mod.f90 /exe:foo.dll

然后,您将从生成的DLLfoo.dll中调用getFoo(),类似于下面的Python脚本

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))

运行这个脚本会产生如下结果,

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

与您的F2PY代码相比,上面的Python脚本可能再次显得相当冗长。但它比您的实现更专业、更现代、更符合标准,既符合Python标准,也符合Fortran标准。

脚注:英特尔ifort免费提供给所有学生、教师和Windows、Linux和Mac平台上的开源开发人员。这并不意味着gfortran不好。但在我看来,在Windows操作系统上使用gcc通常只不过是一场永无止境的噩梦(我与英特尔没有任何关系,只是一名用户(。

最新更新