Fortran best practices: writing Fortran compatible with f2py

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?

You can still use the derived type by introducing a single global instance in the module, also known as the singleton pattern:

type(mytype), private :: singleton

All your f2py-compatible subroutines will then be wrappers of the type-bound methods,

  subroutine alloc(val)
    use myobjects, only: singleton
    real(real_kind), intent(in) :: val
    call singleton%setarr(val)
  end subroutine
2 Likes

In the long term, couldn’t the Fortran compiler simply create proper wrappers for any Fortran feature?

That is my long term goal for the LFortran’s Python wrapper generator (src/lfortran/codegen/asr_to_py.cpp · b602bc287c1d80d6770b0dd56bfa9276b7b2ae39 · lfortran / lfortran · GitLab) to just be able to do. If anyone is interested in helping out, definitely let us know. We are looking for help with this.

4 Likes

@certik, definitely interested in helping in my spare time.

Also, @ivanpribec I just sort-of put together a way to initialize multiple instances of a fortran derived type in python: GitHub - Nicholaswogan/f2py-with-derived-types: Example for how to use f2py with Fortran derived types with type bound procedures . Basically, the idea is that when a python class is initialized, you allocate an instance of the derived type and return a pointer to it. The pointer is stored as an attribute to a Python class. This pointer is used to interact with the instance of the derived type.

It does require a bunch of work though :(.

2 Likes

@nicholaswogan awesome and thanks! For the Python wrappers, the lfortran --symtab-only is sufficient, and the ASR should already work with derived types and some simpler classes. So now the only work is to figure out how to best wrap that using iso_c_binding and then put that into the asr_to_py file. Let me know once you have some time and we can meet over video to get this done, or at least started.

1 Like

@certik I’m pretty busy until Nov 5th. I’ll send you a message around then. Or just @ you in this thread. Then it would be great to meet and chart a path forward!

Quick question though about overall structure. So asr_to_py will use asr from some fortran code to generate setter and getter functions + wrappers with iso_c_binding for procedures written in pure fortran. Then it will generate the needed Cython code to interact with these setters and getters and wrappers?

2 Likes

Perfect!

Yes. We can add more options beyond Cython, but we started with Cython. We can also brainstorm how to best wrap Fortran features via the C interface.

1 Like

@certik With the RST will it be possible to wrap something like this:

subroutine returns_arr1(arr)
    integer, allocatable, intent(out) :: arr(:)
    allocate(arr(10))
    arr = 12
  end subroutine

The best idea I have is calling the subroutine two times. One time gets the dimension of arr, and the second actually returns arr.

Also, it seems like you absolutely have to have the intent(out). Since passing by reference is basically impossible in python.

1 Like

Yes, we definitely will have to figure out how to wrap subroutines like that. The way you described is one possible approach. There might be others.

It can be done without calling the subroutine two times. After calling the subroutine, you can make a pointer to arr, then pass the pointer to cython, where the proper size numpy array is allocated, then go back into fortran, where you can dereference the pointer and copy arr to the numpy array.

So I managed to be happy with how I got my Fortran code working with f2py wrapping. All it requires is for you to not have the derived type be sent to/from the Python side. What I mean is, you can have programs with derived types. Say you want a function you call from python; you call it with inputs, and on the Fortran side, you declare/initialize your derived type and do whatever magic you want with it.

The way this works for me is I looked at what the PETSc team does for their f2py interface; they basically only use f2py -h to generate the appropriate .c and .f90 files, and then use the C and Fortran compilers of choice to compile the wrapper. I used gcc and gfortran. I note gfortran 4.8.5 didn’t work, whereas gfortran 9.3+ did ( I didn’t try everything in between :slight_smile: ).

This seems to work just fine. I even have type-bound procedures on my derived type and everything!
NOTE: Another thing is of course always specifying intent. If I put in the intent lines, it seems like f2py recognizes everything just fine and I don’t need to do any f2py-based inlining/editing. Thank goodness!

1 Like

I’ve moved from f2py to Cython. Cython allows wrapping of derived types and pretty much any feature in fortran. Only drawback is that it must be done by hand, which is a bit slow.

I’ve put together a few examples here: GitHub - Nicholaswogan/fortran-cython-examples

@certik I have some time to work on the LFortran python wrapper. Should we do a zoom call? You can email me: wogan@uw.edu

1 Like

Awesome, I just emailed you.

@certik, Is this issue, the best place to continue discussion for what we want the LFortran python wrapper API to look like?

1 Like

Yes, or you can open up a new one and link it from there.