I’m wondering the best way to write fortran compatible with f2py
. f2py is really great, but it, for the most part, only supports fortran 90 features: No derived types, limited support for pointers. Therefore, you can’t use true object-oriented programing that is f2py compatible. My current work around is to use global data in the following way
All global data is stored in a module, or a few modules
module mydata
implicit none
integer, private, parameter :: real_kind = kind(1.d0)
real(real_kind), allocatable :: arr(:)
end module
Then subroutines explicitly import this global data, and allocate it, or use it to perform some calculation
module mysubroutines
implicit none
integer, private, parameter :: real_kind = kind(1.d0)
integer, parameter :: err_len = 1024
contains
subroutine alloc(val)
use mydata, only: arr
real(real_kind), intent(in) :: val
if (allocated(arr)) then
deallocate(arr)
endif
allocate(arr(10))
arr = val
end subroutine
subroutine printarr(err)
use mydata, only: arr
character(len=err_len), intent(out) :: err
err = ""
if (allocated(arr)) then
print*,arr
else
err = '"arr" is not allocated, so I it can not be printed'
return
end if
end subroutine
end module
This works great with f2py. In an ideal world, f2py could deal with derived types with type bound procedures. In this world I would write the code like this
module myobjects
implicit none
integer, private, parameter :: real_kind = kind(1.d0)
integer, parameter :: err_len = 1024
type mytype
real(real_kind), allocatable :: arr(:)
contains
procedure :: setarr
procedure :: printarr
end type
contains
subroutine setarr(self,val)
class(mytype), intent(inout) :: self
real(real_kind), intent(in) :: val
if (allocated(self%arr)) then
deallocate(self%arr)
endif
allocate(self%arr(10))
self%arr = val
end subroutine
subroutine printarr(self, err)
class(mytype), intent(in) :: self
character(len=err_len), intent(out) :: err
err = ""
if (allocated(self%arr)) then
print*,self%arr
else
err = '"arr" is not allocated, so I it can not be printed'
return
end if
end subroutine
end module
Question: Does this seem like a good way to write f2py compatible Fortran? What other ideas do you have?