Traits, Generics, and modern-day OO for Fortran

Thanks @kkifonidis, great job on the design, it’s well-done, I recommend people to read your document and to provide feedback. I am going to call the current committee’s design (and the current LFortran prototype implementation) a function-based design, and your proposal an OO-based generics design. (OO stands for object oriented.)

The OO-based design seems to contain the function-based design as a subset. Still strong concepts, very robust, explicit, etc. but even simpler syntax, see below for a comparison. In addition, the OO-based design provides a very clean and seamless extension to handle OO as well in a clean, consistent approach.

The function-based generic subset can be compared on this example. Here are the current function-based generics in LFortran:

function simple_sum{T, add, T_cast}(x) result(s)
require :: operator_r(T, T, T, add), cast_r(T, T_cast)
interface operator(+)
    procedure add
end interface
type(T), intent(in) :: x(:)
type(T) :: s
integer :: i
s = T_cast(0)
do i = 1, size(x)
    s = s + x(i)
end do
end function

And here is the corresponding code in the OO-based generics:

function simple_sum{INumeric :: T}(x) result(s)
type(T), intent(in) :: x(:)
type(T) :: s
integer :: i
s = T(0)
do i = 1, size(x)
    s = s + x(i)
end do
end function

Here is the definition of the operator_r and cast_r requirements in function-based generics:

    requirement operator_r(T, U, V, binary_func)
        type, deferred :: T
        type, deferred :: U
        type, deferred :: V
        pure elemental function binary_func(lhs, rhs) result(res)
            type(T), intent(in) :: lhs
            type(U), intent(in) :: rhs
            type(V) :: res
        end function
    end requirement

    requirement cast_r(T, cast)
        type, deferred :: T
        pure elemental function cast(arg) result(res)
            integer, intent(in) :: arg
            type(T) :: res
        end function
    end requirement

here is the corresponding definition of the INumeric interface in OO-based generics:

abstract interface :: INumeric
  integer | real(real64)
end interface INumeric

Or you can specify the allowed functions explicitly:

abstract interface :: IAddable
  function add(self,other) result(res)
    deferred(self), intent(in) :: self, other
    deferred(self) :: res
  end function add
end interface IAddable

abstract interface, extends(IAddable) :: INumeric
  function cast(self,i) result(res)
    deferred(self), intent(in) :: self
    integer, intent(in) :: i
    deferred(self) :: res
  end function cast
  generic :: operator(+) => add
end interface IAdmissible

Finally, to use (instantiate) the generic function, you have to provide an implementation of the add and cast operations in both designs. In function-based generics you would do:

    pure elemental function cast_integer(arg) result(res)
        integer, intent(in) :: arg
        integer :: res
        res = 0
    end function
...
    s_i = simple_sum{integer, operator(+), cast_integer}(a_i)

And in OO-based generics you would do:

implements (INumeric,IPrintable) :: real
  procedure :: add, cast, output
end implements real

contains

function add(self,other) result(res)
real, intent(in) :: self, other
real :: res
res = self + other
end function add
...

    s_i = simple_sum(a_i)

It seems both designs are almost (if not completely) equivalent on this function-based subset. In addition, the OO-based design also naturally include OO-based generic programming.

We should choose the best design for Fortran, with good natural simple syntax, and if OO is to be included either now or in the future, then I suggest to choose such syntax that allows to include OO-based generics in a consistent way. The above proposal is one such way to do it and the best I have seen so far.

6 Likes