To add another advantage of PDTs to those listed by @FortranFan: PDTs allow programming with constrained types in the style of type-dependent programming and this allows for better domain-driven design.
Of course, it is not full (and not even half) type-dependent programming but it is somewhat passable.
It seems the current generics design allows (=does not close doors) to “templated derived types”.
Just a reminder that you can already play with a prototype implementation of the currently proposed generics at https://dev.lfortran.org/. If there is anybody here interested in driving this prototype effort, please let me know! I am doing what I can, but right now my main focus is on coordinating our team and getting LFortran to just compile existing codes (making excellent progress!). We have the manpower to implement things, but I need somebody thinking about the design, the syntax, what new things to implement, testing existing prototype, report bugs, and work with our team to get them fixed. You don’t actually have to fix it yourself, I will help getting it done.
Not sure this would work, or at least it seems it would defy the whole purpose of having less lines of code, as I think you still need to define
subroutine sort(self,array)
class(generic_sorter(4)), intent(in) :: self ! 4 or something else, it has to be a compile-time constant
real(self%rkind), intent(inout) :: array(:)
end subroutine
So you would end up having to multiply the implementations… no? from what I’ve seen in different tutorials/blogs, PDTs seem to be more of a generetic data types, rather than for generic procedures… unless you code the algorithm in a .inc and then just multiply the procedure declaration with an include… not too pretty
You get the right point, i.e., what does the standard allow as far as type-bound procedures with parameterized derived types? Would appreciate any references to what’s (not) possible with this combination.
For me one of the biggest problems with trying to use PDTs for generic programming has nothing to do with PDTs themselves but more to do with how KIND parameters are implemented in all compilers that I know about except for maybe NAG. Namely, both REAL64 and INT64 have a value of 8 so there is no way to differentiate between them other than their names. Why do I feel this is important? Because it prevents you from using PDTs to do something like this.
type :: generic_container(gkind)
integer, kind :: gkind
type(gkind) :: val
end type
type(generic_container(REAL64)) :: a ! real64 value
type(generic_container(INT64)) :: ia ! int64 value
Note in either F08 or F18 (don’t remember which) you are allowed to use type with intrinsic data but only with a very clumsy syntax
type(real(REAL64)) :: a
If REAL64, INT64 etc and the values returned by KIND, SELECT_…_KIND were unique (say REAL64 had a value of 18 and INT64 had a value of 8) then type could be used to define intrinsic variables in a more logical way. Unfortunately, the current KIND facility is to ingrained in most existing compilers that changing it to make the KIND parameters unique is impossible (except for maybe NAG) so we are stuck with a PDT facility that is “mostly useless”. I see this as yet another example of how modern Fortran suffers from short sighted decisions made by previous Standards committees. Making KIND parameters have unique values should have been mandated in the standard but I guess it wasn’t to appease the people who insisted on continued use of real*8 or real(8)
Yes, the current Fortran standard provides for generic interfaces, not generic procedures. A major advantage (some might even argue the only benefit!) with a good, built-in facility in a language toward generic programming is minimizing code duplication. The current standard, to aid its support toward generic interfaces, only provides the INCLUDE facility to minimize code duplication; however, working with INCLUDEs has significant drawbacks.
So the work by the /Generics subgroup in the J3 committee is to provide for the latter starting Fortran 202Y in a manner which does not resort to INCLUDE files.
However the second use case with generic programming shall be generic containers.
Fortran was among the first, going back all the way to mid-1950s, to offer a built-in container with generic arrays of any object!.
Modern applications using Fortran in almost any domain can really benefit from building on this. Here, learning from and extending the PDT design and making it functional/usable toward generic containers, rather than throwing away the baby with the bathwater, will be good for Fortran.
...
template matrix_t(t, plus, times, n)
requires elemental_oper(t, plus)
requires elemental_oper(t, times)
integer :: n
private
public :: matrix
type :: matrix
type(t) :: elements(n,n)
end type
...
end template
As you can see, it has this “matrix” derived type, that has a member of a templated type t.
Can you formulate what is missing from this design? I know that you cannot have templated classes for now, but the door is not closed to it either, it’s just that they are exluding that in the first iteration. It’s not limiting, since you can use derived types and functions to achieve the same.
The syntax is one thing, I don’t have a strong opinion on that right now, since the “surface level syntax and semantics” can be changed (in my mind), it’s independent of the feature itself. As an example, the current existing PDT (the motivation of this thread) seems very limiting, and that’s independent of the syntax and surface level semantics. The feature itself seems limiting. On the other hand, the generics, as proposed, seems to not be limiting. But I will only know for sure once it is implemented in a compiler.
Once it is implemented, THEN I would like to play with the syntax and surface level semantics and gain some experience using it, and tailor it.
I strongly recommend the committee to have a stage in the standardization process, when we actually play with the syntax and semantics, and adjust it to work well. And treat all the current “syntax papers” are preliminary.
RE the example page below, how about including an example of a generic “vector” or “list” type that supports T % append() or T % push() to grow the vector (list) automatically? (via alloc/dealloc with size x 2 etc rather than expensive a = [a,x]). I feel it is one of the simplest and useful cases, but seems missing from examples.
These examples demonstrate how templates can be used to solve certain kinds of problems. It is recommended to explore them in order of increasing complexity as follows:
swap
sort
find
error_handling
matrix
At the “surface level”, I feel the keyword requirement seems unintuitive or awkward because it implies a sentence like “type X requires a requirement” etc in future explanations. To me, “trait” or “concept” seems much more clear and makes code easier to read (even if they are more special keywords or not “Fortranic”).
Another “surface” point is that I feel repeated appearance of contains makes a code much less readable (because the code becomes “A contains B which contains C which contains D”). Is this contains keyword really necessary…?