New generic procedures feature

They were added with an eye toward future generic programming features. The generic procedures feature in the upcoming revision will make them useful. I.e.

generic subroutine swap(x, y)
  type(real, integer, logical), intent(inout) :: x
  typeof(x), intent(inout) :: y
  typeof(x) :: tmp
  tmp = x
  x = y
  y = tmp
end subroutine
9 Likes

@everythingfunctional is this the competing proposal to the generics subgroup? Both will be accepted?

2 Likes

Yes, both are being accepted. They work differently and serve different purposes. Templates are for cases you want to be able to work with types you don’t know about yet. Generic procedures are for when you know all the types you want to work with ahead of time.

12 Likes

8 Likes

Hm, in my mind they serve exactly the same purpose, it’s just a different way you write the requirement, in fact that’s likely how we will implement it also. The type(real, integer, logical) in my mind is just a type T with a requirement real | integer | logical meaning only those types can work. In fact it’s been requested to be able to write requirements in this way, see the examples in Traits, Generics, and modern-day OO for Fortran, such as Traits-for-Fortran/Code/Fortran/functional1.f90 at 51778c3a6ca47c9eda20e4450fe81708c67398b2 · difference-scheme/Traits-for-Fortran · GitHub.

How do these templates work differently? I can’t see any difference, except the slightly different / incompatible syntax? It would be good to unify it. Do you also call it with the ^() syntax to specify exact types?

1 Like

Because they are not templates, they are just a shorthand for writing out multiple specific procedures and putting them behind a generic name. They are “pre-instantiated” with those types, the specific procedures are included in a generic-spec with the name of the procedure, and the specific procedures do not themselves have names. A somewhat silly example:

program example
  print *, my_sum([1, 2, 3]) ! 6
  print *, my_sum([1., 2., 3.]) ! 6.
  ! print *, my_sum([(1., 0.), (2., 0.), (3., 0.)]) ! invalid, not defined for complex
contains
  generic function my_sum(a)
    type(real, integer), intent(in) :: a(:)
    typeof(a) :: my_sum
    my_sum = sum(a)
  end function
end program

vs

program example
  print *, my_sum^(integer, sum)([1, 2, 3]) ! 6
  print *, my_sum^(real, sum)([1., 2., 3.]) ! 6.
  print *, my_sum^(complex, sum)([(1., 0.), (2., 0.), (3., 0.)]) ! (6., 0.)
contains
  function my_sum(T, s)(a)
    deferred type :: T
    deferred interface
      function s(a)
        type(T), intent(in) :: a(:)
        type(T) :: s
      end function
    end interface
    type(T), intent(in) :: a(:)
    type(T) :: my_sum
    my_sum = s(a)
end program

I imagine generic procedures will be used more by application developers, but templates will be used more by library developers.

5 Likes

It gets instantiated for all kinds also, right? So:

  generic function my_matmul(A, B) result(C)
    type(real, integer, complex), intent(in) :: A(:,:), B(:,:)
    type(real, integer, complex) :: C(:,:)
    C = matmul(A, B)
  end function

How is this going to work:

  • will it instantiate all combinations, including “real :: A” and “integer :: C”?
  • How will dispatch on result type work? (I am guessing the result cannot be generic, so maybe we would need to pass C as an intent(out) argument.)
  • What if you split the intent(in) line into two lines type(real, integer, complex), intent(in) :: A(:,:) and type(real, integer, complex), intent(in) :: B(:,:), will they be instantiated as all combinations also?

It seems it should do all combinations per variable, as that would be consistent and independent how you write it. Assuming 3 kinds per type, we get 9^3 combinations, so 729 instantiations that the compiler would have to do for a simple matmul. That seems like a lot. I think it would be much better to do it “on demand”, at “instantiation” time.

Unless the compiler can somehow know that A, B, C should all have the same type and kind, but how would it know it?

Now let’s consider a more realistic example, say the gemv Lapack operation, here is is how it looks like for a complex type:

subroutine zgemv 	( 	character  	TRANS,
		integer  	M,
		integer  	N,
		complex  	ALPHA,
		complex, dimension(lda,*)  	A,
		integer  	LDA,
		complex, dimension(*)  	X,
		integer  	INCX,
		complex  	BETA,
		complex, dimension(*)  	Y,
		integer  	INCY 
	) 	

There are 5 variables that should be generic: ALPHA, A, X, BETA, Y. The function is doing y := alpha*A*x + beta*y (plus optional transposes). Let’s do just “real” and “complex”, a modern compiler might have 4 kinds per type, so total of 8^5 = 32768 instantiations.

It would be realistic to have even more generic variables, say 8, then you have 16 million instantiations, which even the fastest compiler will be very slow at doing.

Actually, also the M, N, LDA, INCX and INCY would be good to have generic for 32 bit and 64 bit integers. If we assume independent instantiation, that’s another 2^5=32 (at least) options.

So something has to give. The easiest would be to somehow tie the different variables together, that’s what Lapack does (only 4 total instantiations: real single/double and complex single/double), maybe times 2 for the two kinds for the integers dimensions, so 8 total, which is reasonable. I think this would be done with the typeof(x) like you did for swap above, correct?

So here is how I would answer my questions:

will it instantiate all combinations, including “real :: A” and “integer :: C”?

Yes. So you want to be careful with this, and use typeof(x) whenever possible to lower the number of instantiations.

How will dispatch on result type work? (I am guessing the result cannot be generic, so maybe we would need to pass C as an intent(out) argument.)

It won’t dispatch on results, so the function result cannot be generic.

What if you split the intent(in) line into two lines type(real, integer, complex), intent(in) :: A(:,:) and type(real, integer, complex), intent(in) :: B(:,:), will they be instantiated as all combinations also?

Yes, both are equivalent and both will be instantiated with all combinations. So you want to be careful and use typeof(x) whenever possible.

@everythingfunctional let me know if I got it right.

3 Likes

No, you have to list the kinds as well, or use kind=*.

As written, yes, but as you point out

generics aren’t distinguishable on result type.

Listing multiple arguments in a single declaration is treated as if they were declared with separate statements. I.e., you get all combinations. You have to use typeof and separate declarations to get “same type” arguments.

You are correct, you can easily end up with lots of combinations of different arguments.

Yep.

3 Likes

This is superb. Thanks for listening to the community’s requests and for your hard work implementing them in the best possible and most Fortran-friendly way. I can imagine how difficult it is to design such an extensive set of new rules and language syntax that could last decades while backward compatible and user-friendly. I cannot wait to reduce tens of thousands of source code lines to mere tens with the new generic syntax. My only question is, do the generics necessitate code generation for all possible combinations at source compile time (potentially leading to code bloating) or only when a specific interface is used?

2 Likes

Since the idea is for the generic subrpograms feature to fully replace usages like

interface generic_name
    module procedure specific_name1
    module procedure specific_name2
    module procedure specific_name3
    ...
end interface

My guess is that all the combinations will be generated.

As for code bloat, that should be up to the linker (not to the Fortran language) —i.e., the linker should have a way to perform dead code elimination.

1 Like

I don’t know if it is only my impression or bias, but I have a gut feeling that in the Fortran world these two guys are rather often the same ninja :thinking: …

1 Like

Per @everythingfunctional’s answer above, it will instantiate everything. But you can use typeof(x) to reduce the number of instantiations.

2 Likes

I found this in the paper 24-148r1,

s19. Ad-hoc specialization shall be performed at compile time, that is,
there will be no trace of the non-chosen specializations in the
generated anonymous specific.
NOTE: This is aspirational, as there is no way at present to express it normatively.

1 Like

Using typeof to implement a smart swap subroutine looks very nice :slightly_smiling_face: I wonder if it should be complemented by:

  • kindof
  • rankof :arrow_left: maybe a plain rank will do.
  • lenof.
  • attributeof.
  • Have I forgotten anything?
2 Likes

For kind=, besides the kind(x) intrinsic, an array can be given, so we’ll finally get to use integer_kinds, logical_kinds and real_kinds from the iso_fortran_env module.

rank seems to be in the works.

For len= we already have… len? :laughing:

And, although I assume attributeof was thrown in as a joke, it might not be too out there: the C 2023 standard also includes a typeof… and a typeof_unqual (for getting the type without const, restrict and so on).

1 Like

@everythingfunctional this seems to suggest that actually the compiler will not instantiate everything, but rather do it on demand at instantiation time. Can you clarify this point?

This is important, as that means this feature is not internally implemented as the usual generic procedure, but rather like the templates that we already did in LFortran, which instantiates on demand, not ahead of time.

This in turn suggests that these two features are very very similar, if not identical, from the implementation stand point. And that in turn suggests the generics subgroup should have a look and unify these two generic features in terms of syntax / semantics, so that we don’t have two independent generics. :slight_smile:

3 Likes

I’ll just point back to

The feature has no notion of “instantiation time”. It is defining multiple procedures at once. Now, a clever compiler can probably delay the actual code generation, but that’s an implementation detail. And if you did delay code generation, you might not find out until later that some combination actually is invalid, which kind of defeats the purpose of knowing ahead of time what all the combinations are. For example say I’ve got some complicated math that I think works for all combinations of numeric types

generic subroutine s(...)
  type(integer(*), real(*), complex(*)) :: a, b, ...
  ...
  if (a > b) then
  ...
end subroutine

relational operations aren’t defined for complex, but if you don’t compile the version with complex arguments, you won’t notice that error.

So maybe you could avoid generating lots of unused code by “delaying instantiation”, but it would be at the cost of detecting invalid code up front.

1 Like

In some situations the programmer would want at least all the possible combinations to pass syntax analysis during compile time, even if all the compiled objects are not generated. In other cases, the programmer might want the fastest compile time for just the combinations of arguments that are used in his program. Regarding the objects themselves, if there are large numbers, say a million or more, of possible type+kind combinations, then generating all of them, and linking all of them together even with only one or two are actually required, would seem wasteful of computer resources and would almost certainly have performance and capacity limitations. There are situations in which the actual types of the dummy arguments are not known at compile time. The design of a consistent and efficient system that addresses all of these possibilities seems like a difficult problem.

1 Like

Actually, the way to catch all these errors is to generate a “requirement” and then simply check that all operations are “allowed” by the requirement. LFortran already does this for the “template generics”.

The above “generic procedures” proposal seems to clearly be designed to be treated as generics, not as brute-force instantiation.

Would you be able to describe how this works? I’m not sure I can.

No it’s not. The resulting generic interface does not work “generically”, only for those specific types, kinds and ranks listed. You’d have to clarify with Hideto (the original author of this proposal), and it’s unfortunate that the term is becoming overloaded so much in Fortran, but I don’t believe his intention was for generic procedures to work “generically”.

For example, there is no intention that a procedure written like

generic subroutine sub(x)
  integer(*) :: x
end subroutine

could be called as

type(my_type) :: x
call sub(x)

Even if my_type had everything sufficiently defined to be perfectly substitutable with integer (assuming that’s even possible).

Again, despite their name (and it is unfortunate), generic procedures are not generic. They are a shorthand for writing multiple specifics.