These kinds of semantics are kind of “up next” for us. My current task is to start coming up with motivating use cases for what it would look like and mean for user defined “collections” to be usable with elemental procedures. We think this will be directly related to how we do iterators as well.
If I want to write an ODE solver that works with a user type containing the model information, I expect a requirement that this user type provides things like initial condition state vector and the function for the derivative of the state vector.
Now I want the state vector to have array semantics (so I can do linear algebra with it) which would be used by the ODE solver. Designing a state vector and implementing the model would be the job of the user of this library, which would allow them to focus on modeling tasks.
Currently to do this you would use arrays of fixed numeric type and pointers to a function with specific arguments that cannot accommodate the user-type describing the system model.
I think chaining functions is crucial for readability when working with these kind of constructs. Obviously this is not possible in Fortran at the moment, but I hope it will one day. We also need proper lambda functions before this is going to be a preferable way of writing code.
That is however completely besides my point which was that the template
scope makes this too limited. I could probably come up with many more examples where it would be desirable to have a type bound procedure be generic over a type U
which is independent of the type declaration itself.
Great! I hope you explore solutions to completely eliminate the instantiate
statements and rather make the instantiation inline with the concrete type declaration or procedure invocation. I think that is realistically the only way to enable type inference which I believe is crucial to make generic code user friendly. I also think that it’s way easier to verbally describe code when it’s done like this. For example type(result_t<integer, error_t>) :: res
can be referred to as “result_t for integer and error_t” whereas I’m not sure how I would refer to type(result_int_err_t) :: res
. My best suggestion is “the result_t type which I instantiated on line ## and named result_int_err_t because it was instantiated for integer and error_t”.
@certik that sounds very interesting, but I have no idea what it involves. Maybe you could explain some more?
We meet once a week, Mondays at 1 US Eastern Time, to work on papers (proposals) for the standard. We are nearly finished with the syntax, and will subsequently be working on uses cases for additional rank-agnostic features, generic iteration, and application of elemental procedures to supported derived-types (i.e. containers). The goal is to be able to support all possible use cases, even if the simple cases still end up needing to be quite verbose. We will then explore ways of abbreviating certain cases. All are welcome to join us and help with this work. Just reach out directly if you’d like an invite.
Great initiative! Timezone differences make that unfeasible for me unfortunately. Are the papers you mention those in the generics repo at the J3 github?

We are nearly finished with the syntax, and will subsequently be working on uses cases for additional rank-agnostic features, generic iteration, and application of elemental procedures to supported derived-types (i.e. containers).
If I understand you correctly, this means that you intend to proceed with the template
scope and the instantiate
statement?

Are the papers you mention those in the generics repo at the J3 github?
The papers in that repository are not the final versions voted on by J3, but they’re not far from it. I’m not sure the general public has access to the papers, but you may be able to access them here: J3 Fortran - J3 Meetings

If I understand you correctly, this means that you intend to proceed with the
template
scope and theinstantiate
statement?
Yes. There are use cases we’d like to support that we were unable to convince ourselves were possible to accomplish with the simpler syntax. But we absolutely do intend to explore possibilities for abbreviated syntax in certain cases.

Yes
Ok. I think this is a huge mistake.
It’s good to go forward with some preliminary syntax, so that we have something to implement in a compiler and something concrete to play with.
We absolutely are not done with the syntax, or even semantics or scope. We only achieved the first step. Now we need to iterate. @plevold why don’t you write down some examples how things could work. @everythingfunctional why don’t you meet with @plevold in a better time slot, so that he can be involved?

@everythingfunctional why don’t you meet with @plevold in a better time slot, so that he can be involved?
I can try and accommodate for some interactive discussions. I find we tend to get the most insights out of worked out example use cases, so for the most productive discussions we should decide what examples to discuss and have them prepared before meeting. I could probably make time to meet Monday or Tuesday week after next (Nov 21 or 22) for a meeting. Just let me know.

@plevold why don’t you write down some examples how things could work.
Honestly I just think that generics should work more like in most other language I can think of that has this feature (Java, C++, Kotlin, Swift, Rust, Go). That is:
- Generics are created by adding type parameters to existing scopes like
type
andfunction
- Generics are instantiated by providing actual types to the type parameters
Also note that of all the languages mentioned above the only one that mentions “template” at all is C++. The scoping rules are still the same as for the other languages.
This is a solution which, contrary to the currently proposed syntax, enables what I believe is three essential requirements:
- A type
T
generic over a typeU
should be able to have a type bound procedure that is generic over a typeE
which is independent of the type declaration - A type
T
generic over a typeU
should be able to have a type bound procedure that takes or returns aT
that is generic over another typeE
- If type parameters can be used inferred from actual arguments it should not be necessary to give them explicitly
I believe items 1 and 2 are clearly demonstrated by the example I show in the original post. I’ll explore item 3 using the not-invented-here syntax in some very basic examples below:
Instantiation with no type inference
Example:
! Declaration of generic subroutine
subroutine print_scalar_sizeof<T>()
requires
type, deferred :: T
end requires
type(T) :: tmp
print *, 'size is', sizeof(tmp)
end subroutine
This generic subroutine has no arguments so obviously type inference is impossible. It has to be instantiated with explicit type arguments:
call print_scalar_sizeof<integer>()
call print_scalar_sizeof<real>()
Type inference for generic subroutine
Example:
! Declaration of generic subroutine
subroutine print_sizeof_array<T>(arr)
requires
type, deferred :: T
end requires
type(T), intent(in) :: arr(:)
print *, 'size is', sizeof(arr)
end subroutine
Here, the type can easily be inferred by the compiler, no explicit type argument is required:
integer, allocatable :: arr(:)
arr = [1, 2, 3]
call print_size(arr)
Partial type inference
Example (same as the one from the LFortran announcement thread):
module add_generic_mod
implicit none
private
public :: add_generic
requirement R(T, F)
type :: T; end type
function F(x, y) result(z)
type(T), intent(in) :: x, y
type(T) :: z
end function
end requirement
function add_generic<T, F>(x, y) result(z)
requires R(T, F)
type(T), intent(in) :: x, y
type(T) :: z
z = F(x, y)
end function
contains
real function func_arg_real(x, y) result(z)
real, intent(in) :: x, y
z = x + y
end function
integer function func_arg_int(x, y) result(z)
integer, intent(in) :: x, y
z = x + y
end function
subroutine test_template()
real :: x, y
integer :: a, b
x = 5.1
y = 7.2
print *, "The result is ", add_generic<:, func_arg_int>(x, y)
if (abs(add_real(x, y) - 12.3) > 1e-5) error stop
a = 5
b = 9
print*, "The result is ", add_generic<:, func_arg_real(a, b)
if (add_integer(a, b) /= 14) error stop
end subroutine
end module
Here, only the first type argument T
can possibly be inferred. One could still allow the compiler to infer this while F
is provided. For example, Rust uses _
for this purpose. I used :
in the example above because that is possibly(?) more Fortranesque.
Explicit instantiation statements
Explicit instantiation could be useful in some situations, but I think aliases (using
in C++, type
in Rust, type
in Go) would be more useful because it could be used to define a new generic:
type :: generic_t<T, U>
!...
end type
! "alias" as a keyword is chosen without very much at random here
alias still_generic_t<U> = generic_t<integer, U>
alias concrete_t = generic_t<integer, real>
These are just examples though. They important part is that I strongly believe that the three previously mentioned statements should be added to the list of requirements. If you believe you have a superior syntax to what I’m sketching out here, by all means go ahead with that.

I could probably make time to meet Monday or Tuesday week after next (Nov 21 or 22) for a meeting. Just let me know.
If you want to discuss further I’m happy to join you in an online meeting. 21. nov, at 14:30 US eastern time (that’s UTC -5, right?) could work for me, how is that for you?
Thanks @plevold, very good progress. Let’s summarize the differences.
1
So instead of:
instantiate add_t(real, func_arg_real), only: add_real => add_generic
print *, add_real(x, y)
you propose:
print *, add_generic<:, func_arg_real>(x, y)
2
Instead of:
template add_t(T, F)
requires R(T, F)
private
public :: add_generic
contains
function add_generic(x, y) result(z)
type(T), intent(in) :: x, y
type(T) :: z
z = F(x, y)
end function
end template
you propose
function add_generic<T, F>(x, y) result(z)
requires R(T, F)
type(T), intent(in) :: x, y
type(T) :: z
z = F(x, y)
end function
Besides these two syntactic changes, are there any semantic changes?

- nov, at 14:30 US eastern time (that’s UTC -5, right?)
That works for me. Feel free to send me a calendar invite, or let me know if you want me to send one.

Besides these two syntactic changes, are there any semantic changes?
Yes, there absolutely is!! Please re-read the following quote from my previous post:

This is a solution which, contrary to the currently proposed syntax, enables what I believe is three essential requirements:
- A type
T
generic over a typeU
should be able to have a type bound procedure that is generic over a typeE
which is independent of the type declaration- A type
T
generic over a typeU
should be able to have a type bound procedure that takes or returns aT
that is generic over another typeE
Perfect, thanks!
I don’t see an example of this in your examples. Can you give a Fortran code example (using your syntax) that shows a “type T
generic over a type U
should be able to have a type bound procedure that is generic over a type E
which is independent of the type declaration” ?
From post #1:
module result_mod
implicit none
private
public :: result_t
type :: result_t<T, E>
requirement
type :: T; end type
type :: E; end type
end requirement
type(T), allocatable :: value
type(E), allocatable :: error
contains
procedure :: is_error
procedure :: and_then
end type
contains
logical pure function is_error(this)
class(result_t<T, E>), intent(in) :: this
is_error = allocated(this%error)
end function
pure function and_then<U>(this, func) result(res)
requirement
type :: U; end type
end requirement
abstract interface
type(U) pure function func_i(value)
type(T), intent(in) :: value
end function
end interface
class(result_t), intent(in) :: this
procedure(func_i) :: func
type(result_t<U, E>) :: res
if (this%is_value()) then
res%value = func(this%value)
else
res%error = this%error
end if
end function
end module
Refer back to the original post for my attempt at implementing this with the current proposal.
Ah I see, thanks. At this point I think I would need you to walk me through it over a video. I understand the use case (I think we want it), but I would need to understand at the semantic level what exactly has to be changed (if anything). Obviously some syntactic changes are needed, but let’s not worry about the syntax at this initial point.
Great, let’s do that! It might be a good idea if @everythingfunctional joins us as well instead of having two meetings on this. Does 21. Nov 14:30 US Eastern work for you as well? I’ll message you both a link for a meeting, but we can change the time if necessary. If anyone else is interested in joining just let me know and I’ll message the link.
Thursday 17. Nov 14:30 US Eastern is one alternative option that works for me.
That should work. Send us a calendar invite and we’ll go from there. If we can’t make it, we can move it.