The Go approach does have a runtime overhead (see Generics can make your Go code slower). The thing that can be problematic with the code analysis approach is that it can be a substantial over-approximation to the number of dynamically called versions of your function.
Thanks to @everythingfunctional, @RonShepard and @certik for the explanations. I think I understand it better now.
We have quite a decent implementation of the subcommittee generics as well as the simple generics in LFortran and it doesnât seem to be an issue. Can you elaborate why you think itâs problematic?
I was thinking that generics calling other generics could be hard to disentangle. Hereâs a silly example:
recursive function f(a,b,c) result(x)
type(int16, int32, real32, real64, complex32, complex64), &
intent(in) :: a(:),b(:),c(:)
type(int16, int32, real32, real64, complex32, complex64) :: x(:)
select case(something)
case(1)
x=f(c,b,a)
case(2)
x=f(b,c,a)
x=f(x,x,x)
case(3)
x=f(b*a,c+a,f(c,b,a))
case(4,etc.)
...
end select
end function
Itâs not impossible to figure out which type combinations would need to have machine code generated but the compiler would have to work at itâŚ
I donât see any compromise to type safety. Each invocation will be to a specific (perhaps unnamed) version with matching argument types, kinds, and ranks.
.jkd2022 wites:
.
- Create machine code for every possible combination of input types.
Wonât this be necessary in the usual case for a generic function, because it will be intended for a library? It would be odd for Fortran to move away from assuming separate compilation. I realize we do get some optimization and debugging benefits from combining routines, which I take advantage of myself.
I am sorry I havenât read any of the proposals, but I havenât seen any comments about how functions that require different executions for different types will be handled. For example, transcendental functions require more code for 64 bits of result than 32 bits. How will the compiler be told which code to use? Is there a straightforward discussion somewhere?
If the code to handle real32
and real64
versions of a procedure differs, one uses the existing ability to define an interface
with module procedure
s. I think this thread is about avoiding the need for code duplication when the same code can be used for different types.
In this case the implementation isnât actually shared, so trying to stuff both implementations into a single template or generic procedure doesnât actually buy you anything but headaches. Just use the existing feature of defining multiple specific procedures in a generic interface and keep the implementations separate.
There are a couple of potential problems with this approach.
First, consider the example given previously of a user-defiined matmul()
that takes real, integer, and logical arguments. The real and integer cases could be written in the same way because additions and multiplications have the same syntax for integer and real types, but the logical case would need to be written differently with .and.
and .or.
replacing the multiplications and additions. How is the best way to handle that situation? Should a single generic be written that has select_type
constructs, or is there a way to combine the single generic with real and integer arguments with the generic for logical arguments into a single overall generic?
Second, when using the existing generic interface approach, there is still the issue of writing portable code that handles all possible kinds for each type. The real_kinds(:)
and integer_kinds(:)
arrays give you the number of kinds of each type and their values, but there is still the next step of using that information in a portable way to write the actual code. And of course, that code would mostly be just repetitions in routines like a user-defined matmul()
, something that these newer proposals are trying to simplify.
Then one can use the template approach to abstract the differences. Like
template numeric_algo(T, op, ...)
type, deferred :: T
interface
elemental function op(a, b)
type(T), intent(in) :: a, b
type(T) :: op
end function
end interface
contains
subroutine stuff(...)
type(T) ...
z = op(x, y)
end subroutine
end template
instantiate numeric_algo(real(sp), operator(+), ...)
instantiate numeric_algo(integer(int64), operator(+), ...)
instantiate numeric_algo(logical, operator(.and.), ...)
Or use a hybrid of the different approaches.
generic subroutine my_algorithm(x, y, ...)
type(integer(*), real(*)) :: x, y
...
end subroutine
generic subroutine my_algorithm(x, y, ...)
type(logical) :: x, y
...
end subroutine
That looks like it addresses this issue.
It looks like the generic name, my_algorithm()
in your example, can be reused for the two cases. What are the restrictions for this? Are the two generic subroutines with the same name required to be compiled together (in the same file, at the same time), or can they be compiled separately?
It would probably be good to show how this would work if you also wanted to support tropical algebra
They could be compiled separately, in separate files. So long as you donât have ambiguous interfaces, you can âcombineâ generic names at any point. I.e.
use mod_a, only: generic_proc
use mod_b, only: generic_proc
interface generic_proc
procedure another_specific
end interface
is valid in a single scope so long as none of the specifics in the one from mod_a
conflict with any from mod_b
, and another_specific
doesnât conflict with any of them.
Iâve worked through a more complicated example that got as far as doing this, but Iâd be curious to see what you had in mind so I could write something simpler. What exactly would you like to be able to do as a user?
Perhaps it is convenient for me to say as a non-compiler-developer, but I would not worry about this at all. If zig and many other languages can do this, so will be possible by the Fortran compiler.
Letâs strive for the best language possible. Compiler devs will manage.
History does not support that optimistic view. Two examples are parametrized derived types and object-oriented programming features. PDTs were introduced in f2003, 20 years ago, and they are still not fully supported in popular compilers. I also have simple, relatively straightforward object-oriented code (extended types, type-bound procedures) that only compiles on recent compilers (if it compiles at all). These are both really good ideas, with significant advantages to use these features, but if one is concerned about portability, they are still not usable, even after 20 years.
@RonShepard sums up my (and I presume others) main frustration with the current status of Fortran (both the standard and compilers). Almost 20 years on from Fortran 2003 and we still have to deal with buggy and/or incomplete implementations of a couple of the really useful features introduced in the last 20 years. There is no excuse for that. We went to the moon in around 10 years. A working and mostly bug proof compiler should not take more than 5.
At the same time other experimental compilers (like LFortran) managed to implement the prototype of generics as an effort of (primarily) one person. I feel safe and certain about the compilers. What makes me less certain is inside-the-box thinking (we cannot design the feature X because it feels difficult to implement, even though it has been clearly already implemented even in small projects like zig or lfortran). Taking into account the development timeline (concept into implementation roughly 10 years), the new Fortran features need to shoot straight into 2030-like programming to be competitive, not barely catch up to 2009 style. The dinosaur needs a good kick in the butt to fly, but if no dinosaur believed it could fly then no pterodactylus would ever take off.
No offense at all towards @certik , but âexperimentalâ is the point here. Compilers like ifort/ifx or PGI are serving operational/industrial projects, and this makes a huge difference. People who are writing/maintaining these compilers are not stupid dinosaurs, but they have to do with operational constraints, and these constraints ultimately depend on the needs of the paying customers.
I have no idea what is your point. Both Lfortran and Ifx are based off llvm (as far as I understand). So was the first version of zig (which has excellent generics). So what is speculated here as borderline impossible has been multiple times demonstrated to be absolutely achievable. If generics are agreed on and passed today, I estimate they land in Ifx in 2025. A bit more optimism
Yes. Also LFortran is not experimental anymore, but alpha quality. You can follow our progress towards beta at https://lfortran.org/.
I think the point is this:
With a sufficient number of users of an API,
it does not matter what you promise in the contract:
all observable behaviors of your system
will be depended on by somebody.
Including the obligatory XKCD