I’ve written a Python C API to the molecular geometry optimization package DL-FIND. The design of DL-FIND requires the user of the package to supply a number of functions at compile time that are later called by the library during runs: dlf_error
, dlf_get_gradient
, dlf_get_hessian
and so on. This design is obviously not compatible with a Python library where the user could dynamically provide different versions of these functions at runtime. My solution to this was to construct dummy functions on the Fortran side that just pass on their arguments to a similarly named procedure imported from the module mod_globals
.
subroutine dlf_get_gradient(nvar, coords, energy, gradient, iimage, kiter, status)
use mod_globals, only: dlf_get_gradient_
use dlf_parameter_module, only: rk
implicit none
integer, intent(in) :: nvar ! number of xyz variables (3*nat)
real(rk), intent(in) :: coords(nvar) ! coordinates
real(rk), intent(out) :: energy ! energy
real(rk), intent(out) :: gradient(nvar) ! gradient
integer, intent(in) :: iimage ! current image (for NEB)
integer, intent(in) :: kiter ! flag related to microiterations
integer, intent(out) :: status ! return code
call dlf_get_gradient_(nvar, coords, energy, gradient, iimage, kiter, status)
end subroutine
mod_globals
stores all the procedures as procedure pointers to the functions obtained from the C (Python) side.
...
procedure(c_dlf_get_gradient), pointer :: dlf_get_gradient_ => null()
...
The abstract interfaces for these functions are defined in the mod_api
module
abstract interface
subroutine c_dlf_get_gradient(nvar, coords, energy, gradient, iimage, kiter, status)
import c_double, c_int
implicit none
integer(c_int), intent(in), value :: nvar
real(c_double), intent(in) :: coords(nvar)
real(c_double), intent(out) :: energy
real(c_double), intent(out) :: gradient(nvar)
integer(c_int), intent(in), value :: iimage
integer(c_int), intent(in), value :: kiter
integer(c_int), intent(out) :: status
end subroutine
end interface
Finally, the way the procedure pointers in mod_globals
get associated to the functions from the C side is by arguments as c_funptr
to the function api_dl_find
that is called from the C/Python side. c_f_procpointer
is used to convert from C pointers to Fortran pointers.
subroutine api_dl_find(... , c_dlf_get_gradient_, ...) bind(c)
...
type(c_funptr), intent(in), value :: ..., c_dlf_get_gradient_, .... ! Functions received from C side
...
call c_f_procpointer(c_dlf_get_gradient_, dlf_get_gradient_)
...
This design for the API seems to work well in my tests with different energy and gradient calculators, but also feels rather hacky. If anyone has any ideas for how to improve or simplify it would be greatly appreciated.
I’m building Python wheels on GitHub Actions, linking statically on Windows and “repairing” the wheels on Linux and MacOS to include the required libraries. Once I make an initial release I will continue with conda-forge packages as well.
Some references:
DL-FIND is also available via Py-ChemShell, but I wanted something that is:
- Leaner and more modular
- Compatible with arbitrary energy and gradient codes
- Available to install as a dependency via package managers