To those interested in enhanced Generics in Fortran:
You may know
“J3” (INCITS), in essence, is a “contractor” to WG5, the body toward ISO IEC standard for Fortran. The “contract” to “J3” is effectively the technical work toward extensions to the Fortran standard.
“J3” is “contracted” with a worklist of items toward the Fortran 202Y standard,
This worklist includes the development of an enhanced facility for generic programming using Fortran,
The meeting will involve technical proposals and voting toward them on a number of aspects toward the Generics worklist item.
The work is headed by a subgroup labeled /Generics
Now, it is my opinion the technical work has long taken a direction that is questionable and worrisome: to a poor, persevering practitioner of Fortran, the future Generics facility per this effort by “J3” subgroup is highly likely to be
onerous
needlessly verbose
a deviation from the existing support in the language that started way back with ANSI FORTRAN 66 with generic (e.g, ABS, MAX, etc.) intrinsic functions and through Fortran 90 facilities and including the latest 2023 standard revision.
I suggest the readers to
study closely the path being taken,
ponder over the concerns I have expressed here and which I will elaborate upon further,
and ask yourself seriously if you agree.
What I wish for is
a petition to the WG5 from the global Fortran Community to consider practitioner feedback in terms of this highly important aspect of Generics in Fortran,
pause any final decision on this feature until
WG5 completes work with another contractor to officially prototype this functionality in an actual processor i.e., Fortran compiler, Here, I would propose LFortran as the candidate toward such prototyping and I am willing to personally fund the effort to a certain extent also, but other processors too can prototype if they so choose.
And that WG5 evaluates a defined set of use cases using this prototype with also input and feedback from (select set of) practitioners in the Community before deciding on the final decision on this feature set in the eventual Fortran 202y official publication.
I am afraid without certain strong and stern actions including evaluation of a working prototype of Generics in Fortran, the work might prove a very poor turn for the language.
Current Fortran generics proposal completely sucks to use.
I do not have the solution and am not a compiler developer, but the current proposal is incredibly verbose, even by Fortran standards.
Modern compiled languages place more burden for features on compilers. If Fortran compiler vendors are not up to the task, perhaps this is just the end of the road for actual Fortran development. Considering most Fortran codebases are in maintenance mode already, it would be a shame, but I suppose not completely unforeseen.
I think WG5 should absolutely require a prototype, ideally in two independent compilers, for such a big feature.
Thanks for your offer to fund the development. The good news is that we have already implemented a prototype in LFortran of the committee’s proposal, together with “simpler” generics.There is also a proposal to implement traits style generics, like Swift does.
@tyranids worked with us to lead the effort as well (thank you!).
To push this further, we just need volunteers to help. If you are interested, please get in touch. Right now I want to use our existing funding for implementing current features, so that we get LFortran in wide use, I think that’s higher priority. It would be no use if we had the best generics, but nobody used LFortran. However, if there are volunteers and/or funding for this, I’ll get you up to speed as well.
I have also pitched it to Intel and Flang to implement a prototype, but I think they don’t have time for it right now.
Last time it was discussed here, it was said that they wanted to set up a “strong concept” first, then spawning some simplified formulations for the most common usage cases. I don’t know if they made some progress towards the simplified formulation, though.
Yep. That’s where not being a compiler developer becomes somewhat an issue. The “first step” they want to make is not a feature I’m interested in using as just a user of the language. Lots of the “and then we can make ABC defaults and XYZ built in this and that” are the only use cases I’m actually interested in.
I sympathize with all the issues raised here, and, I think practitioners should get involved and discuss with the generics group first, rather than WG5 (or even J3), for that’s where the design work is done.
As I understand it, any practitioners are welcome to discuss the developments with the generics team. Have they not been and why not? IMO the generics subgroup has been the most open, forthcoming, and transparent of any J3 subgroups. They have a GitHub repo, discuss here on Discourse, have open calls, present their work at conferences, etc. What more can be done?
Been there, done that, failed miserably. Nothing has worked, everything falls on deaf ears! Similar to “no good deed shall go unpunished,” the motto I find appears to be no good advice shall be heeded.
My own situation is entirely like the AFLAC duck, just don’t get “heard”.
From my point-of-view, the original post here is my absolute last recourse.
Generics is really make-or-break for Fortran, it is high time the Community of Fortran practitioners - those who code in Fortran “in anger” to get involved.
This now has to go to the WG5 level, there just is no other option.
From what I just saw, there seem to be two approaches to generics:
The one where subprograms get the GENERIC prefix —which seems nice, since that effectively eliminates the need for the current INCLUDE approach.
(Although, this one could probably benefit from something like a reusable TYPELIST construct, to replace the (most likely) long list of types allowed for a GENERIC subprogram).
The one with REQUIREMENTS, TEMPLATE, DEFERRED types and INSTANTIATE; which is, indeed quite complex, but seems to have a simplified version —although the simplified version doesn’t seem to allow the use of REQUIREMENTS.
So, I’m all in for the first approach, but the second one still needs some work.
Oh, I was looking at the “Formal syntax (x of 3): templates and instantiation” documents and didn’t see REQUIREMENTS in the examples for the simplified version of templates. My bad!
Wouldn’t adding a type/class-based approach at this point be problematic in terms of implementation?
Sorry for maybe doing poor research, but can the instantiate clauses be put in the “declaration part” of a module or do they have to be written in each subroutine or function separately?
The minimal code for a simple generic scalar copy (not useful at all, just for illustration) seems to be:
module copy_m
template copy_t(T)
type :: T
end type T
contains
subroutine copy(from, to)
type(T), intent(in) :: from
type(T), intent(out) :: to
to = from
end subroutine copy
end template
end module copy_m
Is there a shorter way (either existing or planned)?
There are 3 ways of doing the same in the current proposal, as I have understand
This is the way that has been shown, but with the latest changes
module copy_m
template copy_t{T}
type, deferred :: T
contains
subroutine copy(from, to)
type(T), intent(in) :: from
type(T), intent(out) :: to
to = from
end subroutine copy
end template
end module copy_m
This one using the simplified template procedures(STP):
module copy_m
contains
subroutine copy{T}(from, to)
type, deferred :: T
type(T), intent(in) :: from
type(T), intent(out) :: to
to = from
end subroutine copy
end module copy_m
There was a third one called detached template procedures (DTP), I don’t know what happened to it, so it goes something like this
module copy_m
template copy_t{T}
type, deferred :: T
end template
contains
template(copy_t) subroutine copy(from, to)
type(T), intent(in) :: from
type(T), intent(out) :: to
to = from
end subroutine copy
end module copy_m
I think 3rd one is a very good candidate for adding procedures on the fly to the template isn’t it?
module foo
contains
subroutine plusone{k}(i)
integer, constant :: k
integer(k), intent(inout) :: i
i = i + 1_k
end subroutine plusone
end module foo
There’s no need here to provide a function for adding something, because the compiler can know that i + 1_k with i being an integer is always possible.
And what had been discussed some times ago was the possibility to have the same approach but with multiple and listed types:
module foo
contains
subroutine plusone{T}(x)
type(integer .or. real .or. complex), deferred :: T
integer(k), intent(inout) :: x
x = x + 1
end subroutine plusone
end module foo
Again, the compiler can know that x+1 is always possible because x has a numeric type. Is this approach considered or not?
I think that feature is called generic procedures and this was a request from the Japanese J3/WG5. Generic procedures also takes the kind and rank as well. As for the last example
module foo
contains
generic subroutine plusone(x)
integer(*), intent(inout) :: x
x = x + 1 ! this will become x = x + 1_kindof(x)
end subroutine plusone
end module foo
Here the integer(*) is compiler dependent and it will expand into all the necessary kind for the x. I think there was something like rankof(), so in a similar fashion the committee should consider a kindof() as well. The kindof can come very handy when the computation require different kinds for the calculation, without us manually defining it.
The above example can also be written as
module foo
contains
generic subroutine plusone(x)
type(integer(*), real(*), complex(*)) :: T
typeof(T), intent(inout) :: x
! or just
! type(integer(*), real(*), complex(*)), intent(inout) :: x
x = x + 1
end subroutine plusone
end module foo
From what I understand is that type, kind and rank are built into the template using the deferred keyword
module foo
contains
subroutine plusone{k}(i)
integer, deferred, parameter :: k ! again, this is from the latest paper
integer(k), intent(inout) :: i
i = i + 1_k
end subroutine plusone
end module foo
Again, the compiler can know that x+1 is always possible because x has a numeric type. Is this approach considered or not?
Seems like they are considering a lot of things at the moment. Even I am not sure what is being considered and what is not, sadly. These 2 papers are the latest and I have to go through them as well for the generic procedures 24-147 and 24-148
@AniruddhaDas Thanks… Indeed it’s a bit difficult to follow what is being done, but at least we can see that several simpler approaches are considered to avoid the verbosity of the full stuff in many cases.
Disclaimer: as I stated in another post I don’t have the knowledge to engage fully in this discussion, so take everything with a grain of salt.
What I’ve seen here looks to me as a good effort, but you are often considering test cases where you have one procedure accepting one (generic) argument. Please, consider also situations where you have to pass multiple generic arguments and perform multiple different operations. If you take a solver as a test case you will see that there are three different data types to be passed (a matrix, a vector and a scalar) and multiple inquires/operations to do with them (matvec, axpy, scalar products). While this is a particular example interesting to me, I also think it is a good minimal scenario of a large class of user needs, and perhaps a good generic/templating strategy could be found while trying to handle this problems as well.
Cheers and thank you to everyone that will engage with this development
Does anyone have a good reference they could point to regarding generics? Something that explains the concepts. I’d like to understand the proposal. Some explanations of generics make it sound very simple. I feel like I’m not understanding the more complex examples of Fortran generics. What would the people working on the Fortran proposal recommend as reading to better understand generics in a more general sense?
The problem with “generics” is that it can mean different things to different people. For folks with more experience with C++ than Fortran, generics usually means templates which I think (and am probably wrong about) is considered a form of static polymorphism. I think some form of generics is indeed needed in Fortran but am sceptical that full blown templates are really needed. I would first try to fix PDTs (the committee’s first attempt at template like facility in Fortran) and then implement the Japanese generic procedure proposal. Full blown templates should be delayed until there is a study (and working prototypes) of how templates are used in other languages and use that information to determine if C++ type templates are actually needed in Fortran. I prefer more “Fortranic” solutions than just adopting a “monkey see monkey do” copy of C++. Sadly, given the committees (past and present) and the compiler developers track record with PDTs I’m sceptical anything other than another overcomplicated, bloated feature that has little practical use in scientific programming will be implemented.