Generics in Fortran 202Y: Petition to WG5?

This is why I would use [ rather the {. Brackets are more distinctive than braces.

1 Like

This is like 85% of debugging time for any Matlab programmer who attempts to use cell arrays, especially if the cells contain matrices.

A new video from @everythingfunctional explains how generics will work. Which of the papers at the GitHub generics repo or elsewhere should one read to understand what has been approved by the committee?

2 Likes

Thanks!

Thank you for the very nice presentation @everythingfunctional !

I have to admit, the more I see the “instantiation symbol”, ^ the more I get used to it (unlike the component symbol %, which I never got used to).

I’d suggest starting with https://j3-fortran.org/doc/year/24/24-125r5.txt , https://j3-fortran.org/doc/year/24/24-126r4.txt and https://j3-fortran.org/doc/year/24/24-127r4.txt . Keep in mind that these are subject to change as the work progresses.

There’s also the related “generic procedures” feature requested by Japan: https://j3-fortran.org/doc/year/24/24-147r1.txt and https://j3-fortran.org/doc/year/24/24-148r1.txt

1 Like

The following are relevant as well: https://j3-fortran.org/doc/year/24/24-130.txt, https://j3-fortran.org/doc/year/24/24-131.txt, and https://j3-fortran.org/doc/year/24/24-133.txt

1 Like

I know I’m alone here but I kinda like the ^() syntax. I feel it sits well with the rest of the language.

@everythingfunctional Great video! I think I finally understand fortran generics properly. One small observation, at 16:49 it reads:

instantiate axpy(
    a_type = real(sp), &
    x_type = integer, &
    y_type = real(dp), &
    times_result_type = real(sp), &
    plus_result_type = real(dp), &
    plus = operator(+), &
    times = operator(*)), mixed_axpy => axpy
)

print *, mixed_axpy(a, x y)

And in this simple case I think instantiate axpy(...) => mixed_axpy would be more intuitive as it reads “instantiate axpy onto mixed_axpy”.

It would similarly make sense on the next more complex example at 20:00:

template vector_tmpl(T)
    type, deferred :: T
    type :: vector
        type(T), allocatable :: items(:)
    end type
    contains
        function begin(v)
            ...
        end function
        function end(v)
            ...
        end function
        function next(v)
            ...
        end function
        function item(v)
            ...
        end function
end template

instantiate vector_tmpl(integer), only: &
    integer_vector => vector, &
    integer_vector_begin => begin, &
    integer_vector_end => end, &
    integer_vector_next => next, &
    integer_vector_item => item

If instead the instantiate statement were:

instantiate vector_tmpl(integer), only: &
    vector => integer_vector, &
    begin => integer_vector_begin, &
    end => integer_vector_end, &
    next => integer_vector_next, &
    item => integer_vector_item

It would read:

  • instantiate vector onto integer_vector
  • with begin provided by integer_vector_begin
    etc

This would be a departure from the existing rename syntax. The way the existing syntax works is more like “associate this name with that thing”.

I agree that in this case, the second appearance of axpy seems awkward and redundant. axpy is the name of a template, but what we want to give a name to is the procedure produced from instantiating that template, which doesn’t really have a name at all. I’m starting to think about how to adjust the syntax for this case. As I think about it, it might be more accurate to do something like

procedure(), parameter :: mixed_axpy = axpy^(...)

I’ll bring it up in the next meeting of the generics subgroup.

2 Likes

Why not just swap the positions?

instantiate mixed_axpy => axpy(
    a_type = real(sp), &
    x_type = integer, &
    y_type = real(dp), &
    times_result_type = real(sp), &
    plus_result_type = real(dp), &
    plus = operator(+), &
    times = operator(*))
)

Isn’t this closer to the module rename syntax?

use blas, axpy => daxpy

Also why is the word instantiate needed at all? Isn’t it redundant? I know that they use this word in C++ jargon (although not in the source code), but why not something else like specialize, substantiate, generate, concretize, import, associate, create, …

1 Like

This is probably workable. We’ll consider it.

You need something there to distinguish it syntactically from a pointer assignment statement. I.e.

new_name => tmpl(...)
vs
ptr => something(...)

We did explore different options for the spelling of the keyword, and instantiate is what won. Not to say that it’s definitely the best, but the spelling doesn’t affect the functionality in any way, so spending much time bike shedding over it doesn’t seem worth it.

2 Likes

Thanks, I can see how that would be a problem (similar to the one with statement functions).

Concerning naming, I think it is important. A more common or understandable English word would potentially be easier to translate into other languages.

A similar problem is the misnomer that std::vector is in C++, which is at odds with what most think of as vectors in mathematics. Or the confusingly overloaded keywords like extern and static.

1 Like

@everythingfunctional what is the current syntax for the following example (that works in LFortran today):

    pure function generic_sum{T, add, cast}(A) result(res)
    require :: operator_r(T, T, T, add), cast_r(T, cast)
    interface operator(+)
        procedure add
    end interface
    type(T), intent(in) :: A(:)
    type(T) :: res
    integer :: n, i
    res = cast(0)
    do i = 1, size(A)
        res = res + A(i)
    end do
    end function

    pure elemental integer function cast_integer(arg) result(r)
    integer, intent(in) :: arg
    r = arg
    end function

    pure elemental real function cast_real(arg) result(r)
    integer, intent(in) :: arg
    r = arg
    end function

    subroutine test_template()
    integer :: a_i(10), i, s_i
    real :: a_r(10), s_r
    do i = 1, size(a_i)
        a_i(i) = i
        a_r(i) = i
    end do
    s_i = generic_sum{integer, operator(+), cast_integer}(a_i)
    s_r = generic_sum{real, operator(+), cast_real}(a_r)
    print *, s_i
    print *, s_r
    if (s_i /= 55) error stop
    if (abs(s_r - 55) > 1e-5) error stop
    end subroutine

I am preparing the voting post, but want to give examples.

People will have other meanings in mind for a common word, which search engines will reflect. For example, searching for “Fortran simple function” will give many links that are not about the Fortran 2023 feature of simple procedures.

1 Like

It would look like

    pure function generic_sum(T, add, cast)(A) result(res)
    requires operator_r(T, T, T, add)
    requires cast_r(T, cast)
    interface operator(+)
        procedure add
    end interface
    type(T), intent(in) :: A(:)
    type(T) :: res
    integer :: n, i
    res = cast(0)
    do i = 1, size(A)
        res = res + A(i)
    end do
    end function

    pure elemental integer function cast_integer(arg) result(r)
    integer, intent(in) :: arg
    r = arg
    end function

    pure elemental real function cast_real(arg) result(r)
    integer, intent(in) :: arg
    r = arg
    end function

    subroutine test_template()
    integer :: a_i(10), i, s_i
    real :: a_r(10), s_r
    do i = 1, size(a_i)
        a_i(i) = i
        a_r(i) = i
    end do
    s_i = generic_sum^(integer, operator(+), cast_integer)(a_i)
    s_r = generic_sum^(real, operator(+), cast_real)(a_r)
    print *, s_i
    print *, s_r
    if (s_i /= 55) error stop
    if (abs(s_r - 55) > 1e-5) error stop
    end subroutine
1 Like

If the generics proposal is adopted, eventually compilers will handle the provided code. Before then, could a tool be written that creates an interface to generic_sum with various module procedures so that it works with a Fortran 2018 compiler?

Yes, we plan for LFortran have have such a transformation for all features that are not supported by other compilers (there will be quite a few).

@everythingfunctional what should the poll contain? Here is one idea:

Please select preferred syntax for instantiating (and declaring) templates:

* [ ] `{}`
* [ ] `^()`
* [ ] Other (please comment below)

You can check multiple options. (If you like both, check both.)


Full example for `{}`:
...
Full example for `^()`:
...

I’d add options for, plain parens () and square brackets []. I’d also make clear that the ^ is only for inline instantiation. Other than that it looks good.

A tool could almost certainly be written, but using a generic interface is probably not how you would want it to work. It’s possible certain combinations of instantiation arguments would produce procedures that don’t have distinguishable arguments. For example the cast and add functions could be different, but that doesn’t change the interface of generic_sum. More likely you’d want to find all the instantiations, generate the specific procedures with different names and replace the call site with the right name. With full templates you’d probably generate a whole module for each instantiation and replace the instantiate statement with a use statement.

1 Like

Next iteration:

Please select preferred syntax for instantiating (and declaring) templates:

* [ ] `{}`
* [ ] `^()` for instantiation, `()` for declaration
* [ ] `[]` (there might be issues with parsing due to coarrays)
* [ ] `<>` (definitely issues with parsing due to less than operator `<`)
* [ ] Other (please comment below)

You can check multiple options: check all options that you like. Some of the options
might have issues with parsing as indicated, so a compiler prototype is needed
and they might not be feasible. But we can still vote in terms of the syntax.


Full example for `{}`:
...
Full example for `^()`:
...
Full example for `[]`:
...
Full example for `<>`:
...

If we are going to add [], then we might as well add <>. There is an issue with parsing <> but I think there might be an issue with parsing [] also (although it would be consistent with function calls and array access being the same, so now f[...](...) would look like coarrays too — although we probably don’t want that).

However now when thinking about it: I probably like {}, [], <> in this order. It would be nice to somehow extract that information out of the votes. Any idea how to structure the poll to allow us to do that?