bind(c) is good, but not enough.
I have tried many packages already, f2py, f90wrap, gfort2py ,bindto, all can’t call Fortran’s type bound methods.
bind(c) is good, but not enough.
I have tried many packages already, f2py, f90wrap, gfort2py ,bindto, all can’t call Fortran’s type bound methods.
I think you cannot have bind(c) procedures inside a derived type. A derived type can be bind(C) (act as a struct) but contain no functions or subroutines.
Yeah, this:
module m
use iso_c_binding
implicit none
type, bind(C) :: foo
integer(c_int) :: x
contains
procedure, pass(this) :: inc => foo_inc ! type-bound
end type foo
contains
! Underlying implementation, C-interoperable
subroutine foo_inc(this, a) bind(C, name="foo_inc")
use iso_c_binding
type(foo), intent(inout) :: this
integer(c_int), value :: a
this%x = this%x + a
end subroutine foo_inc
end module m
won’t compile because you cannot have the bind(C) procedure in there:
a.f90:7:10:
7 | contains
| 1
Error: Derived-type 'foo' with BIND(C) must not have a CONTAINS section at (1)
a.f90:14:22:
14 | subroutine foo_inc(this, a) bind(C, name="foo_inc")
| 1~~~
Error: Variable 'this' at (1) is a dummy argument to the BIND(C) procedure 'foo_inc' but is not C interoperable because it is polymorphic
a.f90:14:22:
14 | subroutine foo_inc(this, a) bind(C, name="foo_inc")
| 1~~~
Error: Type 'foo' of CLASS variable 'this' at (1) is not extensible
Something you may consider is to employ bind(C) for your type, create a bunch of bind(C) procedures, then dynamically compile and link to Cython. Finally import your Cython module into your python script.
I’ve done this for procedures, not for types, but I believe it is feasible.
Moreover in Cython you can also create a so called “Extension type”, aka cdef class, and “bundle” your Fortran type and all the procedures into a single cdef class with its methods.
You find some information about using C libraries from Cython here: Using C libraries — Cython 3.2.0 documentation
If you want to C-bind a fortran derived type with procedures, you need:
type :: objcmpl
integer(int32) :: n
real(real32), pointer :: array(:)
character(len=:), pointer :: name
contains
procedure :: print => objcmpl_print
end type
! Initialization function
pure function objcmpl_init(n, value)result(p)
implicit none
integer(int32), intent(in) :: n
real(real32), intent(in) :: value
type(objcmpl), pointer :: p ! Pointer to your object that will passed around on the side C as a void pointer
allocate(p)
allocate(p%array(n))
allocate(p%name, source="F OBJECT"//c_null_char)
p%n = n
p%array = value
end function
! print function
subroutine objcmpl_print(self)
implicit none
class(objcmpl), intent(in) :: self
print *, self%name
print *, self%n
print *, self%array
end subroutine
! C binded function for initialization
pure function objcmpl_capi_init(n, value)result(p)bind(c)
implicit none
integer(c_int), intent(in), value :: n
real(c_float), intent(in), value :: value
type(c_ptr) :: p
type(objcmpl), pointer :: fp
fp => objcmpl_init(n, value)
p = c_loc(fp)
end function
/* COMPLEX DERIVED TYPE*/
/* Methods defined in Fortran for C interoparibility */
extern void * objcmpl_capi_init(int n, float value);
extern void objcmpl_capi_print(void *o);
/* Let's write a C struct that encapsulate the Fortran derived type void* and its methods defined above*/
/* It will look like we are using the Fortran derived directly */
/* We can use the same names as the ones defined in Fortran */
struct objcmpl{
void * fobj;
void (*print)(struct objcmpl *);
};
// C wrappers prototypes
struct objcmpl * objcmpl_init(int, float);
void objcmpl_print(struct objcmpl *);
// C wrapper for the print function
void objcmpl_print(struct objcmpl *self){
objcmpl_capi_print(self->fobj);
}
// C wrapper for the initialization
struct objcmpl * objcmpl_init(int n, float value){
struct objcmpl *self = (struct objcmpl *)malloc(sizeof(struct objcmpl *));
self->fobj = objcmpl_capi_init(n, value);
self->print = &objcmpl_print;
return self;
}
Once you have the C binding you can use Cython as mentioned by @moriglia.
Apart from f2py or gfort2py, most of other the available wrapping methods will require some knowledge of C (and/or C++):
Some of these are also listed under the CPython recommended third-party tools for creating Python extensions. ctypes is probably the easiest, if you just have a few (large) procedures and don’t mind the ABI issues.
As @mskocic has already recommended, when it comes to type-bound procedures you’ll essentially need to “flatten” everything into opaque pointers (these serve as handles).
In case of polymorphic types, when you call the type-bound methods, you need to make sure you associate the opaque C pointer with a non-polymorphic type (rationale: the size and layout of the object must be known to make the association). Building on the example above, something like this:
! extern void objcmpl_capi_print(void *o);
subroutine objcmpl_capi_print(o) bind(c)
type(c_ptr), value :: o
type(objcmpl), pointer :: p
! optionally, check pointer is valid/initialized
call c_f_pointer(cptr=o,fptr=p) ! fptr must be non-polymorphic
call p%print()
end subroutine
It’s your own responsibility to keep track of the dynamic type once on the C (or Python) side. Note this only applies if you are using polymorphism and inheritance.