Prototype implementation of Fortran generics in LFortran

Agree! This is something similar to what I proposed here: More flexible SELECT TYPE · Issue #38 · j3-fortran/fortran_proposals · GitHub

I haven’t been following the generics syntax development closely… but in my mind, if it’s done right, then EVERY Fortran library should be written with generic kinds (not just real(*), but so we can use any user defined type for things like integration or differentiation or whatever). Then we can really have a true composable library ecosystem in Fortran. If this isn’t possible or if it’s too verbose or cumbersome, that’s not going to happen, so it will fail, and Fortran along with it.

2 Likes

The too verbose/cumbersome trap is very real. No one will care if some feature is added that is so perfect for the compiler and internal representation and so “strong,” but completely incomprehensible to the majority of Fortran users. Look at products that are successful in the world. It’s not the most complicated, most perfect, most ideal that wins - it’s the simplest, easiest to scale, and most mass appealing that gains widespread usage. See standards as well. Easy to understand, implement, and use are the keys to successful programming language features.

1 Like

It is really, really, really bothersome to see

  1. the introduction of some new semantics with , CONSTANT here when the standard already has , KIND
  2. that there is any discussion or second-thoughts around this which lead to the comment, “we’re considering requires valid_real_kind(K)”:
  • This has to be a no-brainer if the pursuit is strong concepts

Not including such a “requirement” with parameterized derived types in Fortran 2003 is among the aspects that limited its usability and which perhaps also made it confusing for the few implementors and their few (and mainly) C++ programmers who did the PDT implementations full of bugs and gaps.

Fortran should now consider:

 integer, kind :: K => < real_kinds >  !<-- notional syntax to convey K here belongs to the set of REAL_KINDS

I find KISS principle being entirely overlooked with Generics thus far:

  1. Fortran only needs a template for a variable (object), notionally describable using
generic, object :: G
   type => ..  ! what types can this generic object describe
   kind => ..  ! what kinds of types does it cover
   rank => ..  ! what ranks can the object have
   attribute => .. ! and what attributes: nonpointer+nonallocatable or pointer or allocatable
end generic

(Note GENERIC is already a statement in the standard, the above simply makes it a construct as has occurred with other semantics in Fortran e.g., WHERE, FORALL, etc.

  1. Then, once you have the generic object to work this, Fortran simply needs to allow:
    a. Genericized (aka templated) interfaces,
    b. Genericized (aka templated) subprograms (SUBROUTINEs/FUNCTIONs),
    c. Genericized (aka templated) derived types.

that work with the generic object(s) and help avoid code duplication while delivering simplicity and compactness to the practitioners.

That is it. Anything more or other than this will be unworkable complexity for the practitioners and it is likely to be an unused overkill.

1 Like

I think we all agree on this. It seems you are ridiculing the “strong concepts”, but that’s what Go is using, which you like (based on your replies above). Let’s focus on what the solution should be. If you have time, please help us with the prototype implementation as well as the design of the generics in general, we really need help.

I agree with @jacobwilliams above.

In order for this to happen, all of you should help out.

Not to derail or start excessive argumentation… The idea of “strong concepts” is good. They should not be equated to extremely verbose, multiple definitions. I believe many examples have been given in this very thread to provide strong checking capability at compile time without excessively verbose syntax.

1 Like

@certik / other moderators:

Starting with this comment, the subsequent discussion appears to be on simple generics / templates as opposed to prototype implementation in LFortran. It may thus be worth moving the comments to this other thread - hope it isn’t too much trouble.

@certik,

You have the right idea, something compact like this which, within it, does indeed have strong concepts built into it is what will be sought by almost all the practitioners and many implementors (e.g., Paul Richard Thomas of gfortran in communication to @longb back in 2018).

Note in my example above, I used

  1. numeric_type instead of numerical
  2. angle brackets (< .. >) instead of curly ones.

Readers, please note I am not at all hung up on these symbols and characters and labels or anything like that, all I care about is whether the facility is simple and compact for the practitioners and does not bring in anything at all superfluous that will inevitably become onerous for the Fortranner.

Note the standard already has terminology and definition for numeric type:
image

and note an intrinsic SUM is only applicable for this class of intrinsic types:

That is the only reason I brought up numeric_type from a design goal the new Generics facility being attempted for introduction into a nearly 70 year-old language should also try to bring in only a minimal amount of new syntactical elements while using as much of the standard terminology that has already been published officially.

The use of angle brackets < .. > is illustrative for it is already in wide use in programming such as with Java, C++, C#, and so forth and markup languages, etc. If the parsers for Fortran can do with some other combo, so be it.

2 Likes

Thanks @FortranFan. Yes, numeric is even better, especially if it is already defined in the standard.

I created:

Simpler templates · Issue #1838 · lfortran/lfortran · GitHub

To get this done in LFortran. We can do the implementation, but we really need somebody to volunteer to be a “technical project manager” to create examples, and issues to fix. I will organize the actual fixing. The technical manager will test the implementation, report bugs, prioritize issues for us to fix, etc. We need somebody who will be thinking about this long term, and ensure our implementation will work for the end user. The skills required: enthusiastic about Fortran and generics. That’s it.

4 Likes

Sorry I haven’t been able to respond over the last few days. I was busy and travelling back home. At any rate, we (Generics Subgroup) are fully aware that there are “simpler” use cases that seem like they ought to be possible with less verbose syntax, and we agree. It’s on our to-do list to come up with the syntax for that.

However, the suggestions provided so far in this thread have some general flaws that would prevent generalisation and future improvements. Subgroup is working hard not to put together something “half-baked” that later needs to be deprecated and redone. The poster child for this is forall. It was deprecated in favor of a new feature, do concurrent, because it wasn’t going to be backwards compatible to extend in the ways that were needed. PDTs seem to have experienced a similar fate, and one would have hoped they could have been used for generic programming.

One of the popular suggestions so far have been “we just want a generic ‘numeric type’ declaration.” But what exactly are the details of that specification? Is it only applicable to intrinsic numeric types? If so, then the algorithms written in those terms aren’t as reusable as one would hope, the feature falls short, and is unusable for future extensions.

If it is possible to write new “numeric” types as a user, what are the requirements to do so? Do I need an implementation for every intrinsic that takes an intrinsic numeric type? Is complex numeric? But it can’t be used with the max intrinsic. So can the max intrinsic be used with “numeric” types?

If you write a generic sort algorithm, is it possible for me to instantiate it with less-than and greater-than swapped so I can sort in reverse order?

We’ve got several use cases and examples available in our GitHub repo:

Any proposal for a “simpler” generics needs to be usable to implement those use cases and examples, or at least extensible in a backwards compatible way that enables them in the future. Trust me when I tell you that isn’t an easy design challenge, but I do welcome suggestions.

4 Likes

Yes, we need to be able to do all those.

Yes, suggestions are definitely welcome. But we also need help beyond that: we need help with prototype implementations and figuring out all the details and in general we need help with pushing this forward.

Apologies if I’ve missed something, but in all this talk of simplified generics we seem to talking about how to specify that the function takes specific types. Have we instead considered the possibility of specifying that a function takes specific behaviours? Something like (I’m completely making up syntax here)

function sum(xs)
    generic(T), dimension(:), intent(in) :: xs
    generic(T) :: sum
    applicable :: operator(+)(T, T) result(T)

    integer :: i

    if (size(xs) == 0) then
        error stop
    end if

    sum = xs(lbound(xs))
    do i = lbound(xs)+1,ubound(xs)
        sum = sum + xs(i)
    end do
end function

function mean(xs)
    generic(T), dimension(:), intent(in) :: xs
    generic(T) :: mean
    applicable :: operator(+)(T, T) result(T), operator(/)(T, integer) result(T)

    mean = sum(xs) / size(xs)
end function

function dot(xs, ys)
    generic(T), dimension(:), intent(in) :: xs
    generic(U), dimension(size(xs, 1)), intent(in) :: ys
    generic(V) :: dot
    applicable :: operator(*)(T, U) result(V), operator(+)(V, V) result(V), zero() result(V)

    integer :: i

    dot = zero()
    do i = 1,size(xs)
        dot = dot + xs(i)*ys(i)
    end do
end function

If you omit the applicable statements, then the compiler could emit error messages like (imagine I forgot the applicable statement in mean):

ERROR: Application 'operator(+)(T, T) result(T)' is required.
NOTE:  Required because 'sum' requires application 'operator(+)(T, T) result(T)' here:
23:12:    mean = sum(xs) / size(xs)
                 ^

Or if I tried to call mean(['a', 'b', 'c']):

ERROR: No application 'operator(+)(character, character) result(character)' exists.
NOTE: Required because 'mean' requires application 'operator(+)(T, T) result(T)' here:
132:9:    m = mean(['a', 'b', 'c'])
              ^

I feel like this is more in line with the original generics proposal, and could even be made compatible with it, while still being much less verbose.


Although having written all this out, I’m now wondering if it’s still too complex and not sufficiently powerful enough to warrant that complexity… Still, maybe it will spark some extra thought for someone.

This is very similar to what the REQUIREMENT and REQUIRES features are meant to be. It’s also that the place the template is used can decide what the actual procedures are. I.e.

INSTANTIATE SUM_TMPL(REAL, OPERATOR(*)), ONLY: PRODUCT => SUM

@seamsay yes, both the current proposal and the simpler generics talk about “behavior”, not individual types. In one of our examples we had individual types, but we corrected it for behavior — the set of operations and functions that you can call on the template.

Sorry, to bump this thread. I was wondering if the instantiation syntax could be on the right-hand side of the association/renaming:

use sum_module, only: product => sum_tmpl(real,operator(*))

To give a full example:

module reverse_module
  
    implicit none
    private
    public :: reverse_tmpl
  
    requirement default_behavior(T)
      type, deferred :: T
    end requirement
  
    template reverse_tmpl(T)
      require :: default_behavior(T)
      private
      public :: reverse
    contains
        subroutine reverse(array)
            type(T), intent(inout) :: array(:)
            type(T) :: tmp
            integer :: i, j
            do i = 1,size(array)/2
                j        = size(array) + 1 - i
                tmp = array(i)
                array(i) = array(j)
                array(j) = tmp
            end do
        end subroutine reverse
    end template
    
end module

program main
  use reverse_module, only: reverse => reverse_tmpl(integer) :: reverse
  !use reverse_moduly, only: reverse_tmpl
  !instantiate reverse_tmpl(integer), only: reverse
  integer :: a(5)
  a = [1,2,3,4,5]
  call reverse(a)
  print *, a
end program

More than likely not. It conflates several things:

  • bringing the template into scope
  • instantiating the template
  • bringing the instantiated entities into scope
  • renaming the instantiated entities

For example, if you want to either instantiate a template multiple times, or the template defines multiple entities, the use statement becomes a bit cluttered. Also, if you want to instantiate a template that is defined in the same scope, the use statement is not appropriate.

It’s good to keep hearing ideas though.