Attention @everythingfunctional , in the context of this paper, can you please provide the proposed Fortran 202Y syntax for the simple case presented by @certik toward authoring a generic Fortran function that can take any KIND of a floating-type argument and define a function result of the same KIND?
Please see this link for reference to such a function and the discussion on it led by @certik.
The code from the referenced proposal would look like:
template log10_tmpl(k)
integer, constant :: k
private
public :: log10
interface log10
procedure log10_local
end interface
contains
simple elemental function log10_local(x) result(r)
real(k), intent(in) :: x
real(k) :: r
r = log(x) / log(10._k)
end function
end template
Youād then call it like
use kinds_m, only: wp
instantiate log10_tmpl(wp)
real(wp) :: x, y
x = 42._wp
y = log10(x)
Can you please explain what led to the need for an interface construct with the template construct even in such a simple case? Because what you show is likely to be seen as more verbose than necessary, it is likely to end up as being unwieldy for many Fortran coders.
What are the aspects the Generics subgroup think that would prevent a simple TEMPLATE that defines the KART i.e, kind, attribute, rank, and type characteristics of an entity and for the language to include templated module procedures which can then work off of the template entity, a la procedure interfaces now in the language? For example,
module m
..
template T(k)
use, intrinsic :: iso_fortran_env, only : real_kinds
integer, kind :: k := real_kinds <-- some such syntax to indicate 'k' belongs to real kinds set
end template
..
contains
..
simple elemental function log10<T>(x) result(r) !<-- some compact syntax to indicate templated module procedure
real(k), intent(in) :: x
real(k) :: r
r = log(x) / log(10._k)
end function
..
end module
! caller
use m, only : log10 !<-- this should suffice to `USE` log10 on the caller side
use kinds_m, only : WP
..
real(WP) :: x, y
..
y = log10<WP>( x ) !<-- simple **in situ** compile-time instantiation
The points include:
building on current semantics to auto export interfaces whenever viable i.e., take advantage of what is built into the language with module procedures,
bringing in a new integer, constant aspect for KIND appears not needed. Why not reuse the integer, kind semantics with parameterirzed derived types when dealing with entities that indeed correspond to KINDs?
you will find coders will feedback that in situ compile-time instantiation of templated subprograms is a must e.g., y = log10<WP>( x ) above.
if Fortran seeks strong concepts and I agree itās right for Fortran to have this, then let it be strong: whether itās integer, constant :: k or integer, kind :: k, the context here is a KIND for an intrinsic REAL type only and nothing else. Then there should be a way to strongly inform the processor the kind constant belongs to the REAL_KINDS set and nothing else. That way the template parameter of said template is only used to template the KIND of REAL types connected with the template and nothing else.
@FortranFan I can imagine later adding some simpler syntax for this common case, such as the one from the J3 Fortran Proposals repository. The main issue for me is to ensure the feature is in. As I commented elsewhere, I strongly recommend the committee to later come back and iterate/simplify the surface level syntax where appropriate.
@RonShepard Yes. Do you have a better name than pedantic/strict? Other ideas I have are āsafeā, āsubsetā, āsimpleā, but I donāt quite like any of them.
Apologies: please note I miswrote above implying simpler syntax. Actually what I really meant was simpler semantics. Consider this simple case brought up by @certik: it is truly debatable whether the TEMPLATE construct, as per Fortran 202Y proposal, needs to define a ātemplateā INTERFACE therein only to encapsulate what is a templated procedure in log10_local, as in the illustration by @everythingfunctional above.
Something seriously does not appear right here.
This requires serious thought and for various Fortran practitioners who are deeply interested in Generics such as @plevold and @shahmoradi et al. to think through this deeply and to give feedback which the Generics subgroup must review. If the underlying aspects such as these are not designed well, there will be no later simplification or enhancement viable, the feature will be doomed and a lot of practitioners will not use it. Fortran needs to get Generics right.
I will bring up the possibility in subgroup tomorrow to suggest that āall procedures defined in a template are implied to be provided in a generic interface with their given nameā (or something similar), but I am not yet certain that there arenāt potential complications. What if Iād rather provide it as an operator? Or put multiple of the procedures defined in a single template into a single generic interface? Or define a type and type-bound procedures? Thereās multiple more complicated cases to think through than to just assume it will work.
What do people think about comptime as Zig has implemented? It really seems like an amazing system that is powerful, expressive, and rather concise in notation. Documentation - The Zig Programming Language
Such a facility would allow generic programming, as well as better inform the compiler of calculations and constants that should be known at compile time. If they cannot be resolved, compilation error.
Iām a big fan of generics being added to Fortran, but think @FortranFan is dead on - if the capability is excessively verbose/complicated to use, or so convoluted that future changes are deemed impossibleā¦ thatās a major setback to generic programming in Fortran. We know if a half baked feature is added, then removal will be impossible (backwards compatibility), but fixing it may very well be impossible as well (backward compatibility)
@FortranFan yes, the simplification that you want is what I think of as āsurface level languageā. If we implement this āany kindā feature into LFortran, we can later use the simpler syntax and simpler surface level semantics and the compiler frontend generates the same intermediate representation. I think there is no door closed.
@tyranids yes, I am familiar with Zigās style generics and have mentioned it to the Fortran Committee members. Roughly speaking there are two main approaches: generics (types) and metaprogramming. The current Fortran proposal is just generics, not metaprogramming (which however could be added later). Zig is an example of metaprogramming: executing code (in this case Zig code) at compile time that can operate on types. In order to ensure that the generics are not half-baked, we have implemented a compiler prototype and are asking for feedback. Before they get standardized, we should get enough experience with it to ensure that the feature truly fixes what users have been asking for, in a simple enough syntax with all the features in. Indeed, your concern is why I voted against many features that I considered half-baked, which might be impossible to get fixed later. Generics must be fully baked.
I think the concept of āthis value shall be known at compile time as constant, and if itās not throw a compiler errorā is incredibly valuable. Fortran could start generics there, with the only ācompile time known constantsā allowed in the first pass being kind parameters. That would allow one to write code like
pure function realsumplus2(xin<rk>) result(xout<rk>)
integer, comptime :: rk !! this value is known at compile time to be a constant
!! and therefore can be substituted in source code as an integer parameter
real(rk), intent(in) :: xin(:)
real(rk) :: xout
xout = sum(xin) + 2.0_rk
end function realsumplus2
This type of function definition inherently defines the interface as well: the input argument xin must be real(kind=rk), and the corresponding output value xout is of type real(kind=rk). To be fully transparent, my example syntax here is completely off the cuff and very well may be fatally flawed. However, I will maintain my original point: " I think the concept of āthis value shall be known at compile time as constant, and if itās not throw a compiler errorā is incredibly valuable. Fortran could start generics there, with the only ācompile time known constantsā allowed in the first pass being kind parameters." The reason this is good is twofold: 1) it is immediately useful as my example above, and 2) it is not overly restrictive such that future expansion is pre-emptively made impossible.
The standard only includes the semantics of a processor constant (ācompile timeā in ordinary parlance) with the KIND clause to the integer type e.g.,
integer, kind :: k
There is really no need to invent constant or comptime or any other term to signify the same.
@tyranids do you want to help prototype this in LFortran? I think we have all the pieces in place already and I can help you. If we can have more people pushing these generics, it would be incredibly helpful.
I would be happy to have āinteger, kindā extended to somehow indicate a variable-in-source-but-known-as-constant-at-compile-time value. Itās very reasonable to not want new keywords for every new feature, but I am not sure how to go about that really in a way that wonāt draw ire from the (majority?, at least) many champions of backwards compatibility. If existing keywords and syntax is somehow repurposed or changed in functionality, how does that not break somebodyās code, somewhere?
Letās discuss this further. I am coming around on personally contributing to some FOSS Fortran compilers. If everyone says ānot me,ā then who will?
I could imagine this kind of declaration might be written in an extended way as
integer(kind=kind(j)), kind :: k
To my eye, those three different uses of ākindā in the declaration look clear and unambiguous. However, if there is some kind of syntax ambiguity here, then it should be addressed early. If necessary, perhaps the KIND of k could be restricted to only the default integer kind?
I think part of the key is somehow indicating that integer, kind :: k is a ācompile-time input argument that must be unambiguously known for each entry to this scope.ā I think the syntax suggested earlier like function<WP>(args) is good, as the different type of bracketing on <WP> indicates that this is still a potential list of values, but they are somehow different from (args). Perhaps k would be declared as integer, intent(comptime), kind :: k, to indicate its value belongs in the <brackets> of function calls.
As I type the above, I am still not seeing why this need be restricted to kind values. The value of k is known at compile time to be constant, if the compiler cannot verify this - compilation error. Next, for each unique k in all references to function<k>(args), compile a separate version of function, with the value of k propagated throughout functionās source. If this were a Fortran-language level task, a human programmer should find/replace all instances of k in functionās scope with the compile-time known constant to achieve the desired effect.
In a PDT, an integer with the KIND attribute can be used in other ways, such as for array lengths. The KIND attribute means that the value is known by the compiler at compile time, unlike the LEN attribute which might be known only at run time. An integer with the LEN attribute cannot be used to specify KIND values. I think both can be used in expressions, for example to initialize component values. As Iāve said before, I have wanted to use the PDT feature many times over the last 20 years, but there have always been compiler bugs in some of the compilers that I use that have prevented that widespread use. I hope that same thing does not happen for this template feature.
@certik, as you will note, in the context of Fortran and especially its standard, there is no such thing as a āsurface level languageā.
You can view things however, but that is largely immaterial: what really matters is
first, what the implications are for the practitioners of Fortran. If even for the simple case you present, if the practitioners are required to needlessly set up INTERFACE constructs and whatever while giving the appearance of āstrong conceptsā but not having all the guardrails for it, then again the facility will be half-baked for practice and lead to great consternation and disuse,
second, how the larger set of implementors manage with the new facility. If the LLVM-based processors and IBM Fortran and gfortran and NAG and Intel, etc. are unable to navigate the complexity whereas itās a breeze for LFortran or other newer better-designed processors from the ground-up, it still is a massive problem.
Thus KISS should apply and a simple measure of it is whether for simple cases, the facility for the practitioners first and the implementors next is simple enough. I am not seeing that at the moment and thatās my concern.
I did bring up this aspect at the meeting. The general sentiment was that phrases/behaviors that are āimplied,ā āas-if,ā or āautomaticā are not really āFortranic.ā Not to mention that it potentially closes the door on other use cases, or at least makes the standard and implementations much more difficult. I.e. the template writer wants to put several of the procedures in a template behind a single interface (a la findloc). You canāt put generic names into a separate generic interface. You also canāt specify generic names as type-bound procedures. So procedure names defined in a template automatically being generic names did not seem popular, and seems to cause more problems than it solves. Sorry, the extra line in templates is likely to be necessary for the spelled out version.