Prototype implementation of Fortran generics in LFortran

With the latest LFortran (022dbc29) you can now play with a prototype implementation of the Fortran generics. Here is a demo file that you can try:

You can copy & paste that example into https://dev.lfortran.org/ and it will work:

You can also test it locally:

$ lfortran integration_tests/template_add.f90 
The result is  1.22999992e+01
The result is  14

@tom_clune, @everythingfunctional, @gak, @FortranFan and others, can you please test it out and provide feedback?

LFortran itself is alpha, and the generics are a prototype. Please report any bugs that you discover into issues: Issues · lfortran/lfortran · GitHub, just open up a new one.

Also, we quite urgently need more examples, if the generics subcommittee could create more examples or tests that we could use, that would be awesome.

Many thanks to Oshanath, Luthfan, Ubaid and many others for implementing the initial prototype and making it working locally as well as online. Special thanks to Magne for helping us design it in the compiler.

24 Likes

Absolutely brilliant!!!

2 Likes

@certik ,

Can you and the contributors working on this prototype implementation in LFortran please take a look and consider the Fortran source below which is based on current standard i.e, Fortran 2018 with a rather, simple-minded implementation of a poor Fortranner version i.e., using unlimited polymorphism toward a generic 1-D sort that employs the Cormen’s algorithm?

Using this code, two Fortran compilers help generate the following output from the program:

C:\temp>gfortran kinds.f90 base.f90 string.f90 utils.f90 Qsort.f90 p.f90 -o p.exe

C:\temp>p.exe
Block 1
initial array is  42 999 -1 0 50 12
sorted array is  -1 0 12 42 50 999

Block 2
initial array is  32.0 30.0 75.0 54.0 64.0 66.0
sorted array is  30.0 32.0 54.0 64.0 66.0 75.0

Block 3
Initial array is  q w e r t y
sorted array is  e q r t w y
Block 4
Initial array is  Mary   had    a      little lamb
sorted array is  M      aar    lady   hittle lamb
Block 5
Initial array is
Mary   had    a      little lamb
sorted array is
Mary   a      had    lamb   little

So you will notice the above “generic” code supports 4 kinds of integers, 3 different floating-point kinds, 1 kind of Fortran’s CHARACTER type, and any user-defined type which extends an arbitrary base type has deferred procedures for comparer functions. The calling example program, you will notice, sorts 1-D arrays of 5 different types.

The Generics subcommittee might perhaps be able to help putting together an equivalent example of the above using the new, proposed TEMPLATE facility for Fortran 202X? If so, can it be an example you are looking for?

The reason I suggest something like this is because it is very simple, it does not involve any math or computer science concepts such semigroups, monoids, rings, fields, etc. and so a reader can thus focus on Fortran TEMPLATE facility and its syntax and semantics.

sort.f90 (26.2 KB)

2 Likes

Yes, that would be perfect! Thanks @FortranFan.

It’s ideal, because LFortran currently only has prototype support for “classes”, but strong alpha (approaching beta, but not quite there yet) support for Fortran 90 style features. That way we can just focus on the generic features and get them more developed.

@tom_clune, @everythingfunctional and others, if you could provide the generic version using the latest syntax (as you understand it), that would be awesome, then we can try to implement it.

1 Like

Thanks for prototyping the generics, Certik. This is great.
A more general question regarding generics: I am not entirely familiar with the syntax of generics yet. Does it still require writing two separate implementations for real and integer kinds like func_arg_real and func_arg_int in your example? I am pretty sure that I am missing an essential part of the picture. But if not, the posted example seems unnecessarily complex and redundant for such a simple task.

4 Likes

@shahmoradi so I am getting up to speed on all the details also, but here is my understanding: the generic code is just this:

    requirement R(T, F) 
        type :: T; end type
        function F(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
        end function
    end requirement

    template add_t(T, F)
        requires R(T, F)
        private
        public :: add_generic
    contains
        function add_generic(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
            z = F(x, y)
        end function
    end template

Of which the actual “meat” of the code is just this:

        function add_generic(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
            z = F(x, y)
        end function

That is simple enough I think. It’s saying that F is some operation (to be provided by the user) that operates on x and y and produces z. The user is free to supply any such implementation.

Regarding the user part, you currently do this:

    real function func_arg_real(x, y) result(z)
        real, intent(in) :: x, y
        z = x + y
    end function

    subroutine test_template()
        instantiate add_t(real, func_arg_real), only: add_real => add_generic
        real :: x, y
        integer :: a, b
        x = 5.1
        y = 7.2
        print*, "The result is ", add_real(x, y)
    end subroutine

You provide the actual implementation of the F operation, and you provide the user type, in this case it’s real. That’s it.

Can the compiler “implement” some of these basic operations (such as addition) for types like real and integer and just supply those implementations implicitly? Yes, I think it can and should.

The best way is to see this on actual examples of some useful functions, such as sorting.

2 Likes

+1 :+1:

1 Like

This is very interesting, I’m working on a (still to be disclosed) library and if lfortran’s generics implementation is mature enough by then I will definitely prefer it over python pre processors.

1 Like

I just read the sort example and indeed it’s much clearer. Just call QSortC(my_array).

1 Like

Thank you @meow464

1 Like

So the most complete description of the templating feature is where? I thought the F() procedure could be written in terms of type(T) and so the user did not have to supply a function for each actual type, more like macro expansion, so I am confused, but have not been following this too closely. I was just wondering if there some ability to do conditional inclusion into such a function.

Preprocessors are not
an ideal solution, but something very close in functionality to the sort, but not as fancy (I believe abstract types did not exist when this was written, so I did not even think of going that way – sort.f90 is a great example for abstract types); and looks like it will be a good one for templating as well.

xx.txt (5.8 KB) is an example prep(1) input file for the curious.

If you run that through the prep(1) preprocessor it expands out the code to sort most common integer, real, and character types as well using macro expansion and text block reprocessing; as an example.
I have a decent amount of stuff done with the preprocessor like that; so seeing the sort.f90 procedure as a template (:>) on how to proceed will be useful; as I think some of my processor-dependent stuff should be easy to convert into examples; as I have been using prep(1) or it’s predecessors for a long time.

It is great to a new feature being prototyped; instead of waiting for five years after something is in the standard for a compiler to have it implemented. This is exciting. I was expecting to have a couple of years to learn templating before I could actually use it!

4 Likes

Fantastic work! I can’t wait to see more generics features being implemented and used.

Here’s one use case I stumble upon all the time. I want some generics function to return an allocatable array of a type that is fixed, but from a generic interface:

subroutine my_allgatherv(this,comm) result(gathered)
   class(parallel_type), intent(in) :: this(:)
   type(SAME), allocatable :: gathered(:)
   class(parallel_communicator), intent(in) :: comm
   ! etc
end subroutine

How would that be handled with the current generics features proposal?

Another feature I would really like to see, but I’m not sure it’s really “generics”, is some feature to generalize the numeric kinds (Fortran, where numbers are king!), say:

   ! example 1
   subroutine besselj0(x)
      real(*), intent(in) :: x
   end subroutine besselj0

   ! example 2
   real(BK) function besselj0(BK,x)
      integer, intent(in), kind :: BK
      real(BK), intent(in) :: x
   end function besselj0

   ! example 3
   module my_bessels(BK)
      implicit kind real(BK)

      ! ... use BK as real kind
   end module my_bessels
   
   ! use generic module
   use bessels_64 => my_bessels(real64), only: blabla
2 Likes

Nowhere. There are proposals that passed or are being considered by the committee, but it’s mostly requirement and stuff. The actual surface syntax I think is not settled yet.

The F procedure adds the two arguments of type(T). I think that for arithmetic operations we should figure out a more natural way to do this, especially if the user type will be “real” or “integer”. However, if the user type is some derived type or class, then the user must provide an implementation of this operation (although some shortcuts could be done for arithmetic operations).

In the most general case, the operation F is not an arithmetic operation. It could be something like what in C++ would be T.eval(), some user defined “method”, that for example evaluates a user defined function, and the generic code minimizes it. So the user has to provide this in the most general case.

1 Like

Related question: how should we handle these “experimental” / “prototype” capabilities of new Fortran language features in the compiler?

Should it be disabled by default and you have to enable with a compiler option?

Should it always give a warning message that the feature is a “prototype” or “experimental” and that the syntax and semantics can change? We want to have the freedom to iterate on the design. Initially we did this on a branch, but it’s actually more work for us to now maintain two branches (the main one, and the generics one). So we just have one main branch and it contains generics. The idea is that the generic feature will evolve, we are changing the syntax and semantics as we develop this language feature, with the Fortran committee.

Maybe right now we can just give a warning each time the generic feature is used, so that people know this is experimental. We can keep this warning on as long as we are thinking the syntax or semantics can still change. If or when we decide that the feature will not change, we can remove the warning.

@kargl what do you think would be a good approach here?

1 Like

Just some food for thought in case there is anything to pickup from another compiler and a language: see the link below for some info on what Microsoft does with /c++latest and /experimental switches:

Disabling compiler optimizations with such early features may be another way to ensure users don’t consider using them in their actual codes?

1 Like

I think this is the straightforward case, but there are more general cases that should be considered too. One is the capability to specify the output KIND that is different from the input KIND (such as the intrinsic functions REAL(), INT(), CMPLX(), and so on. Another related case is when the output KIND depends on, but is not the same as, the input KIND. In this case, the output might be a simple mapping of the input

function DPROD(x,y)
SOME_DECLARATION :: MAP(4)=8, MAP(8)=10, MAP(10=16), MAP(16)=-1
real(*), same :: x, y
real(MAP(KIND(x)) :: DPROD
...code to generalize the intrinsic DPROD()...
end

Fortran intrinsics have been able to specify the output kind since KIND was introduced in f90, but that capability has not been exposed to programmers.

I see, yes, we definitely need an std option (possibly called version or lang) to select a Fortran standard and implement it as faithfully as we can. It looks like “std=latest” could be (right now) Fortran 2023 plus this generics experimental feature (Fortran 202Y).

Then we have some LFortran specific changes, such as the implicit none handling. So those could be called “LFortran 2018” or something like that. I believe the gcc compiler does something similar: a C++ standard plus GNU extension.

I think there is a way to do it so that everybody here can get the mode they want.

1 Like

I think this would be a good approach. Also, it should be clear that the syntax might change if/when the feature is standardized and that the old syntax WILL NOT IN ANY SHAPE OR FORM continue to be supported after that occurs. DEC made that mistake with f77, and it continues to haunt compilers still trying to support the old syntax and also programmers who must be fluent in obscure syntax that was never standardized.

2 Likes

Is that with the “parameter” syntax?

I know there is a lot of “prior art” on exactly these mistakes, implementing some feature in a compiler that gets standardized differently and the resulting problems from that.

At the same time, in my opinion compilers have to lead these changes, and the standard should only standardize things that are actually tested and used (how much tested and used is up for discussion).

I think there is a way to walk this fine line, with good warnings and default behavior of the compiler and compiler options. We appreciate any help with designing this well.

1 Like

Looking at the Julia Bessels code, I learnt it has some of these perks, to e.g. ensure that a minimum precision is guaranteed:

function besseli0x(x::T) where T <: Union{Float32, Float64}
    S = promote_type(T, Float64)
    x = S(x)