Python interoperability with Fortran

Here is something that I would like to have in Fortran also:

The example shows Julia code for using a Python library. And if the import is changed, the very same code is also a valid Python code. Thus showing that at this high user level, Julia is very similar to Python.

Looking at the example, it seems it might work in Fortran, if we replace . with %. I don’t know how to best simulate nested modules. I wish the following two proposals somehow could get accepted, because then I think the code would run in Fortran verbatim:

https://github.com/j3-fortran/fortran_proposals/issues/86
https://gitlab.com/lfortran/lfortran/-/issues/84

The last one I didn’t even post at the fortran_proposals repository, as I think the chance is very low at this point. But the first one I think might have a chance.

The other related thought that I have is to have automatic translators from Python and also from C++ into Fortran. The way they would work from Python is that they would take the Python code, and then translate into Fortran, calling any libraries from Python, but the script itself would be in Fortran, with the correct syntax. So you would give it the above script, and it would spit out correct Fortran that you can run. The same with C++. I think that’s technically doable and would go a long way to help people move to Fortran from those languages.

3 Likes

While it would be great to just import Python and C++ libraries, with a module/derived type kind of syntax, two obstacles I see are the strong typing and the call syntax for subroutines/voids. The example from Twitter would end up looking like:

real :: X_train(1000,3), Y_train(1000,1)
real :: X_new(2,3)

model = keras%sequential([&
    keras%layers%dense(10,activation="relu"),&
    kers%layers%dense(1,activation="sigmoid")&
])

call model%compile(optimizer="adam",loss="mse")

X_train = tf%random%normal([1000,3])
Y_train = tf%random%uniform([1000,1])

call model%fit(X_train,Y_train,epochs=2)

X_new = tf%random%normal([2,3])

print *, model%predict(X_new)

Another potential problem is the fact Fortran is case insensitive.

Now for the Python objects I imagine something like:

use, external :: tf => pyimport("tensorflow")
use, external :: keras => pyimport("tensorflow.keras")

or

use PyCall, only: PyObject, pyimport

type(PyObject) :: tf, keras, model

tf = pyimport("tensorflow")
keras = pyimport("tensorflow.keras")

So either you would have some kind of Python code translator that would need to be invoked upon compilation, or to have a special PyObject type as some kind of dynamic runtime object connected to a Python interpreter.

Maybe just an extra-layer in the Fortran compiler which would detect any “pyimported” structures, and translate (source to source) those to the right sequence of calls from the Forpy module. Click here for an interesting blogpost about Forpy.

Forpy can already interface to Python modules, but it is kind of clunky:

program date_demo
  use forpy_mod
  implicit none

  integer :: ierror
  type(module_py) :: datetime
  type(object) :: date, today, today_str
  character(len=:), allocatable :: today_fortran

  ! Python:
  ! import datetime
  ! date = datetime.date
  ! today = date.today()
  ! today_str = today.isoformat()
  ! print("Today is ", today_str)

  ierror = forpy_initialize()
  ierror = import_py(datetime, "datetime")
  ierror = datetime%getattribute(date, "date")

  ierror = call_py(today, date, "today")
  ierror = call_py(today_str, today, "isoformat")
  ierror = cast(today_fortran, today_str)

  write(*,*) "Today is ", today_fortran

  call datetime%destroy
  call date%destroy
  call today%destroy
  call today_str%destroy

  call forpy_finalize

end program
1 Like

Good point, there are more differences. So it would have to be translated anyway. Regarding the syntax, here is what we came up with at https://gitlab.com/lfortran/lfortran/-/issues/44 :

use, external(python) :: tensorflow, only: random
use, external(python) :: keras, only: sequential

There is the ultimate limitation of Fortran imports that you cannot import a module as a namespace, see https://github.com/j3-fortran/fortran_proposals/issues/1.

I would still like to think that derived types can be used to emulate namespaces, even though it is torturous to expose and rename everything:

module foo_mod

  implicit none
  private

  public :: foo_t, foo_
  public :: say_hello_

  integer :: i

  type :: foo_t
    integer :: a = 5
    real :: b(5) = [(i,i=1,5)]
  contains
    procedure :: say_hello
  end type

  type(foo_t), target :: foo_ = foo_t()

contains

  subroutine say_hello(self)
    class(foo_t), intent(in) :: self
    write(*,*) "Hello, World."
  end subroutine

  subroutine say_hello_()
    call foo_%say_hello()
  end subroutine

end module

module bar_mod

  use foo_mod, foo => foo_, say_hello => say_hello_
  implicit none
  private

  public :: bar
  public :: foo, say_hello

  type :: bar_t
    type(foo_t), pointer :: foo => foo
  contains
    procedure :: square
  end type

  type(bar_t) :: bar

contains
  
  real function square(self,x)
    class(bar_t), intent(in) :: self
    real, intent(in) :: x
    square = x**2
  end function

end module

program main

  use bar_mod, only: bar, foo, say_hello
  implicit none

  print *, bar%foo%a + foo%a

  print *, bar%foo%b
  print *, bar%foo%b - foo%b

  print *, bar%square(2.)

  call bar%foo%say_hello()
  call say_hello()

  associate(bf => bar%foo)
    call bf%say_hello()
  end associate

end program

An annoying restriction is that Fortran does not allow using non-intrinsic functions in initialization statements.

A new namespace syntax would make it much easier.

1 Like

I am not against the derived types in this application to emulate Python modules, as it would be automatically generated and allow at least a little bit natural access. The alternative is to do something like this:

use, external(python) :: keras  ! imports everything
...
model = keras_sequential([ &
    keras_layers_dense(10,activation="relu"), &
    kers_layers_dense(1,activation="sigmoid") &
])

I think one could achieve a Python-like syntax as in Julia with derived types, if Fortran had the option to overload the “%-operator”:

The compiler then could translate a statement such as
y = x%get(0)
to
y = type_of_x_overloaded_percent(x, "get", 0)

Since a call to a Python function could have any number of arguments, the procedure that overloads the %-operator would need to accept any number of arguments. Therefore Fortran would also need variadic functions.
Another issue is that you cannot chain method calls with % in Fortran:
A statement like y = x%get(0)%set(1,1) is not allowed in current Fortran.

2 Likes

Another reason why Python modules probably should be represented as derived types is that in Python modules are also Python objects. They can even be passed to functions - although this is probably not used a lot. That is why there is a type(module_py) derived from type(object) (for generic Python objects) in forpy.

Right now what in Python is (assuming the arguments have different types and no keyword argument)

x = model.fit(X_train, y_train, epochs)

would be

ierror = tuple_create(args, 3)
ierror = args%setitem(0, X_train)
ierror = args%setitem(1, y_train)
ierror = args%setitem(2, epochs)
ierror = call_py(x, model, "fit", args)

Maybe with class(*), dimension(..) arguments and Fortran 2018 select rank and select type, one could achieve (up to some maximal number of arguments) the following syntax:

ierror = call_py(x, model, "fit", X_train, y_train, epochs)

If Fortran got exceptions one could get rid of the error code:

x = call_py(model, "fit", X_train, y_train, epochs)

With the “overloaded %” this would finally become

x = model%fit(X_train, y_train, epochs)

This achieves the Python syntax in this simple function call, however I don’t have an idea on how to get Python’s keyword argument syntax.

1 Like

however I don’t have an idea on how to get Python’s keyword argument syntax.

Possibly, by overloading some operator (e.g. => if possible currently or in future) to create some “(key-value) pair” type and pass such temporary objects as arguments (e.g. along this line)…?

x = model%fit(X_train, y_train, epochs, "foo" => 100, "pi" => 3.14)

EDIT: I initially thought that the use of => may be problematic because of its meaning for pointer assignments. But in the above case the LHS is a string literal, so I guess there is no confusion for the overloaded meaning of =>.

1 Like

Interesting, I didn’t know that Julia handles keyword arguments that way.
I guess in standard-conforming compilers something like this will not be implemented any time soon.
But as @ivanpribec mentioned above, the corresponding forpy code could be generated from standard Fortran syntax.

1 Like

Welcome to the forum @ylikx, and thanks for all the suggestions here.

I would like this to eventually become part of our tutorials / guides at fortran-lang.org, especially once we have the tooling to automatically translate, either from Python, or from some extension of Fortran or both. Right now we are just brainstorming what would make the most sense to do.

1 Like

Thanks for the welcome!
I would be interested in efforts regarding compilers (e. g. LFortran), I’ll try to stay up-to-date.

1 Like

Perfect. For LFortran you can follow us on Twitter: https://twitter.com/lfortranorg for the latest updates.

1 Like

It is possible the other way. Can we use the modern Fortran (using c interop) and compile it into a python module. Not using f2py or f90wrap. Using the CPython API. Did anyone do that?

Thank you.

1 Like

In theory yes. But you have to make sure to use the Fortran compiler that is ABI compatible with the C compiler used to produce your Python implementation. I’ve not done it manually. I’ve used f2py once before, and my understanding is that it’s benefit is producing the necessary plumbing to make your code usable from Python with a simple import my_module. Without it you’d have to write that by hand, which doesn’t sound like fun.

1 Like

Yes, you can do it as described here:

https://www.fortran90.org/src/best-practices.html#interfacing-with-python