Traits, Generics, and modern-day OO for Fortran

This announcement is for those of you who have expressed concerns
about the direction that Fortran development has been taking in the
recent past, and who would like to see both an alternative take on
generics, as well as modern-day OO programming capabilities in the
language.

For some time now, I’ve been designing, together with @certik, and
@tyranids, a traits (or polymorphic interfaces) system for
Fortran. Its aim is to endow the language with state-of-the-art
capabilities for both compile-time and run-time polymorphism, that
are only equalled by those of the Swift, Rust, Go, or Carbon
languages.

We have surveyed all these latter modern languages in order to distill
their very best features with respect to polymorphism, and to tie
them into a coherent and consistent package of extensions for
Fortran, that is both powerful, yet easy to use (also for
non-experts), and backwards compatible with the present language.

The result is described in the following document, whose latest
version can always be found on Github, along with the code for all its
examples: Traits for Fortran

The design features:

  • Traits based, flexible, modern-day, OOP (as in Swift, Rust, Go)
  • Traits based, fully type-checked, generics, interoperable with both
    procedural, functional, and OO programming (as in Swift, Rust, Go)
  • Non-necessity for explicit instantiation of generics (as in Swift)
  • Type sets as traits, to easily formulate generics constraints (as in Go)
  • “Zero cost” static polymorphic method dispatch via generics (as in Rust)
  • Interoperability with class inheritance, but also support of “sealed” classes
  • Room for future growth, e.g. for future support of array-rank-genericity,
    or compile-time polymorphic union types

@certik plans to prototype this complete design in the open source
LFortran compiler, once LFortran has reached the point of providing
stable support for Fortran’s legacy polymorphism and OO features.

Yet, I wish to point out that we have explicitly developed this design
for the benefit of the entire Fortran community, not just one
particular project. Our ultimate goal is to give Fortran users the
chance to test out, in actual compilers, all those features of modern
languages that they have been repeatedly asking for, to no avail, in
this forum.

We believe that these capabilities, once they will become widely
available in Fortran compilers, will give the language a significant
edge over its competitors in the fields of numerical, scientific, and
high-performance computing, and will thus help to establish Fortran’s
long-term dominance in these fields.

What you can do to help:

  • If you like our design, express your support! Let us also know about
    any critique you may have. We welcome critique, as long as it is
    constructive.

  • Contribute to the development of LFortran, and other open source
    Fortran compilers, so that this design can get implemented faster!

  • Contact the developers of your Fortran compiler, and let them know
    that you wish to see these features also in their compiler!

  • If you are a Fortran compiler developer, contact us for a
    collaboration!

  • Once we have a first compiler implementation of the design, use it
    and provide feedback, like bug reports, etc., so that we can fix any
    teething issues!

  • If you are proficient in Swift, Rust, Go programming, etc., we’d
    like to hear from you whether there is any feature connected to
    polymorphism in these languages that you are missing, and would like
    to see in the present design.

Regards, Konstantinos

20 Likes

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

I haven’t read the paper on GitHub yet but from these examples the OO version appears to have a simples syntax.
I like it!

2 Likes

On the Vector example, what does this syntax mean? This is new syntax right?

‘’’
self%elements = [self%elements,item]
‘’’

As far as I can tell, that particular line is not new. It’s using allocation on assignment to extend an allocatable array.

4 Likes

The first mention I saw of the ability to extend of an array by allocation on assignment was in the Fortran 2018 version of Modern Fortran Explained. Look on page 109 , Section 6.7 Automatic reallocation. I use it sometimes to extend small arrays but am leery of using it for anything really large due to the potential performance hit caused by the compiler creating a temporary array to hold the resulting extended array and then reallocating and copying to the target array.

4 Likes

From what I’ve read of the paper so far (up to section 6.1), I really like this proposal. I found it easier to read and understand. The explanations and comparisons with go, rust and swift are very good too.

I used to think Fortran generics should be as simple as possible since in practice its main use would be supporting multiple numeric types. But this proposal made me envision Fortran on the same league as Go and Rust abstraction wise.

3 Likes

I’ve had a quick look and like what I’ve seen. I guess I’d prefer <…> over {…} since that’s what other languages use (C++, Rust) but maybe that’s harder to implement in Fortran.

3 Likes

Finally got around to reading the entire proposal (a couple of times because it takes a long time for my procedural programming brain to grasp most OOP concepts) and I’ll add my support for making this proposal happen. On paper this looks like it addresses most of my problems with the current templates based proposal. It appears both simpler to implement and more flexible in what it can do and what it can be. Frankly, I support it for no other reason than its not just some warmed over attempt/kludge to make Fortran work like C++. This has the potential for evolving into a truly “Fortranic” solution to generics etc.

5 Likes

Does the trait proposal support code reuse or is that the role of inheritance?

For example, could I define the following function and use this definition for multiple types conforming to INumeric?

function 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 sum

The first paragraph of the Historical Background section of the proposal I think addresses why inheritance has been found over the years to be a not so great thing, particularly for code reuse. That has always been one of my biggest problems with Fortran OOP is its reliance on inheritance when at the time it was being developed the issues with inheritance were already known and people who were influenced by the Design Pattern research were already moving away from it.

The road towards these realizations was surprisingly long. Over the last five decades, a huge
body of OO programming experience first had to demonstrate that the use of (both single and
multiple) implementation inheritance breaks encapsulation in OO languages, and therefore results
in extremely tightly coupled, rigid, fragile, and non-reusable code. This led to an entire specialized
literature on OO design patterns [4, 6, 9], that aimed at avoiding such rigidity by replacing the
use of implementation inheritance with the means to formulate run-time polymorphism that are
discussed below. It also led to the apprehension that implementation inheritance (but not run-time
polymorphism) should be abandoned [15]. In modern languages, implementation inheritance is
either kept solely for backwards compatibility reasons (e.g. in the Swift and Carbon languages),
or it is foregone altogether (e.g. in Rust, and Go).

5 Likes

For code reuse in modern-day OOP you should use composition instead of implementation inheritance.

In your particular case, you would put that sum function inside a class, SimpleSum, as it is done in the proposal, and you would use that class through composition, as in the PairwiseSum (client) classes of Listings 6.3 and 6.4.

Notice, that these classes depend only on the interface, ISum, that SimpleSum implements. Hence, you don’t have any rigid dependencies in these client classes on actual implementations, which is what keeps your code flexible.

The only way you would make use of the actual SimpleSum class implementation is through its constructor (see the aforementioned listings).

Implementation inheritance should nowadays generally be avoided. We kept it in the design merely for backwards compatibility reasons (as does Swift).

3 Likes

Makes sense.
I really like this proposal, makes Fortran feel like a modern language. A language someone would choose over C++ even for really complex software.

3 Likes

@kkifonidis , @certik ,

Great effort. However based on the immediate and long-term needs of the practitioners of Fortran, any proposal toward Traits, Generics, or whatever that is based on type(T), … should really be a non-starter, absolutely dead on arrival (DOA).

All the examples in the “Traits.pdf” have “type(T) …”

I would give a firm NO to this if I had a vote!

Please review this post recommending KIND, ATTRIBUTE, RANK, and TYPE aspects. as a fundamental building block toward any enhancement toward Generics.

Given all the work in Fortran starting with ANSI FORTRAN 1966 through the current Fortran 2023 revision that has made use of TKR semantics and some ATTRIBUTE and what has been introduced with INTERFACE block, traits or generics based on “type(T)” is too limiting.

You can refine your proposal a lot better via an entity block idea.

@FortranFan we eventually settled in the proposal to use class(T) for runtime polymorphism and type(T) for compile-time polymorphism. Are you objecting to the syntax of (re)using type(T) or are you objecting to how the design itself works? The syntax is less important to me at this point, I mainly care about the design itself.

Can you formulate your objection against the design? I don’t understand it from your comment so far. I think your suggestion might be to not template the type inside type(T), but rather the whole entity in the declaration, so that you can write <T> :: node, so the <T> also includes rank and other attributes.

We can focus on the rank. I think rank is tackled separately in the above OO-based proposal.

@certik, yes “not template the type inside type(T), but rather the …entity in the declaration” is what I recommend. Any by the entity is meant:

  1. KIND parameter,
  2. ATTRIBUTE: allocatable | pointer | nonallocatable, nonpointer
  3. RANK,
  4. TYPE

With this, say a received argument to a procedure is:

real(real64), rank( ), allocatable, contiguous, intent(inout) :: x  !<-- some arbitrary rank; using Fortran 2023 rank clause

then the equivalent representation toward a generic Fortran program as starting with “type(T)” is a no-no, it’s a dangerous recipe for same old issues with Fortran, half-baked features that serve too little, too late.

Instead, consider along the lines of a named entity block, say it’s called E then:

<E>, contiguous, intent(in) :: x  !<-- KART aspects of this entity are defined by E

or

{E}, contiguous, intent(in) :: x  !<-- KART aspects of this entity are defined by E

or

generic(E), contiguous, intent(in) :: x  !<-- KART aspects of this entity are defined by E

etc., meaning the specific syntax is TBD, no need to get hang up on syntax yet and throw things out because someone objects to the parsing challenges in <..> or whatever.

The point remains:

  1. any solution toward Generics or Traits that leads to code examples with “type(T)” is inadequate,
  2. instead, I recommend an entity block built around KART semantics to serve Generics and with generic resolution. This is merely building upon the 58+ years of generic support around the critical TKR semantics in Fortran starting with ANSI FORTRAN 66.

Note @kkifonidis et al. (you’re listed as second author) in the paper in the original post have done an outstanding job based on compile-time and run-time polymorphism to serve Generics and with the smart use of abstract interfaces that have been employed well by other languages, the team has advanced superbly toward simplicity and compactness in Fortran representation.

Yet Fortran can do better and its practitioners can benefit more if you all can refine your concepts further with such feedback.

Keep up the great work,

I believe I understand your request here. Rather than the concept of a class or type at all, you would rather arguments be parameterized on kind, attribute, rank, and type (KART). That can be called an entity or whatever else, but the idea is to group these parts of the definition into a single entity that can be used multiple places. I will note that unless “type” includes user written derived types, that seems less than ideal. Also you would want some way for the entity definition, derived types, and procedures written to work on the entity to all be declared in different places. Otherwise it is impossible to compose your software across multiple libraries. If a KART entity is defined in a library, and many procedures written to use it, then how would I create a new derived type in my own code and use it with those library procedures?

I struggle to think of how you could write generic code that works for an entity of rank 1, 2, or 3, but not rank 4+. Could you please provide an example? I suppose something that the language already handles, like a write statement or intrinsic operators would work, but at that point how is the rank restriction better than writing the procedure as elemental?

Amazing work! It will take me a while to go through your document :sweat_smile: In the meantime, I have a question: how does this compare to Julia’s multiple dispatch?

3 Likes

What we propose in the document doesn’t make use of multiple dispatch. It always dispatches on one object (if that is what you ask).

But it lets you choose whether you want to dispatch dynamically, for increased flexibility, or statically, for increased performance (due to the possibility to inline polymorphic methods by the compiler). This is basically the same that Rust allows you to do.

I am not sufficiently familiar with Julia’s dispatch model to comment on any further differences to this language.

1 Like

Thank you for the clarification :slightly_smiling_face: there is a great presentation about it On YouTube, where the author explains that it has several advantages over other forms of dispatch. If I understood correctly, it’s one of the main features that allow Julia’s code to be reused.