No, this is not accurate - refer to the standard.

Using pointer-rank remapping is a clever idea.
Readers, please note to not allow the specific inside details of the solution toward a generic SUM
to derail the discussion. In the case shown upthread using pointer remapping
, it is merely an illustration of something which is workable per the current standard and yet which is employed toward an illustration toward a language enhancement in a Fortrannic manner without relying much on OO to lead toward Generics.
Note the reason for the use of C interoperability
procedure here is because of a possibility per the Fortran standard starting Fortran 2018 that a rank-generic entity may not referenced in an expression but only in certain inquiry functions such as SIZE
and C_LOC
e.g., an assumed-rank argument cannot be referenced in an expression per current standard.
What I recommend introduced in the language are companion utilities to facilitate Generics, similar to what have employed with COARRAY
s, interoperability with C
, etc. The candidates for such utilities can include:
- an intrinsic
REMAP
subroutine, - a
SWAP
subroutine, c.f. C++std::swap

This is true, but there is also a performance penalty for non-contiguous memory access, so it would be unclear which is more costly.
The ideal programming situation would be for the compiler optimizer to always determine from the code when and how such local copies are made, and to produce always the optimal code. These “copies” might be to scalar registers, or vector registers, or local cache, or local gpu memory, an so on and ideally the compiler can see enough of the code to reuse these local copies as much as possible. If fortran programmers were required to take such details into consideration, then the high-level language would not be very useful. Of course, this ideal situation is not always achieved, some compilers are better than others, there is some code that cannot be optimized by any compiler and must be hand-coded, and there are some reuse situations where the fortran programmer must take responsibiity for creating the contiguous local copy and then using that copy multiple times with multiple subroutine calls, and so on. Another common compiler failure related to this is overallocation of the stack space by the compiler; this results either in a program halt or it triggers some kind of garbage collection that is then observed as sporadic poor performance.

No, this is not accurate - refer to the standard.
Yes, it is.
From Sec. 10.2.2.3, paragraph 8
If bounds-remapping-list appears, … the pointer target shall be simply contiguous
For example, I attempted to compile the following code with the NAG compiler.
program rank_remap
implicit none
integer :: arr(4,4), i
arr = reshape([(i, i = 1, size(arr))], shape(arr))
call print_as_1d(arr(::2, ::2))
contains
subroutine print_as_1d(a)
integer, intent(in), target :: a(:,:)
integer, pointer :: tmp(:)
tmp(1:size(a)) => a
print *, tmp
end subroutine
end program
I got the following error.
Error: example.f90, line 10: Rank-remapping pointer assignment target is neither rank 1 nor simply contiguous
And as for the c_f_pointer
solution, the code compiles and runs, but doesn’t give the correct view:
program rank_remap
implicit none
integer :: arr(4,4), i
arr = reshape([(i, i = 1, size(arr))], shape(arr))
print*, "expected:", arr(::2, ::2)
call print_as_1d(arr(::2, ::2))
contains
subroutine print_as_1d(a)
use iso_c_binding
integer, intent(in), target :: a(:,:)
integer, pointer :: tmp(:)
call c_f_pointer( c_loc(a), tmp, [size(a)] )
print *, "obtained:", tmp
end subroutine
end program
Output:
expected: 1 3 9 11
obtained: 1 2 3 4
I confirm what you observed, and that corresponds to what you already told me some time ago.
After your comment I change my code and I am now using a combination of select rank
and pack
. Which may not be suitable when performance is critical but does the job for me.
Good job on your paper. I must admit that I had no idea what it takes to implement generics into a language and that’s certainly no easy task.
If I can add my two cents, you may want to have a look at how generics are treated in .NET. In particular, it uses constraints on the generic type that I found very handy and would not require defining interfaces like INumerics.
class MyClass<T, U>
where T : class
where U : struct
{ }
Thank you for your hint.
If it is merely the syntax in C# that you find handy, then Rust has a similar where clause: Clearer Trait Bounds with where
Clauses.
I realized recently that we could pretty naturally support this (alternative) syntax also in Fortran, even without a where
clause, as I’ve shown it for a function here:

function sum{T}(x) result(s) INumeric :: T type(T), intent(in) :: x(:) type(T) :: s integer :: i s = T(0) do i = 1, size(x) s = s + x(i) end do end function sum
The main difference between the generics of C# and Rust seems to be that C# allows also things other than interfaces (in particular base classes) as constraints. I am pretty sure they do this in order to stay idea-compatible with their “sibling”, Java, which uses this older (some would say obsolescent) model.
If we would allow this, then we would have dependencies on implementations all over generic code, which would undermine the paradigm. We should better stick to how it’s done in Rust.
I am not sure but I guess that in c# when you constrain your type to a double you are actually constraining it to all the underlying interfaces like IEquatable or ISdditionOperators.
I am not familiar at all with Rust, but looking at it I can see some similarities.
In case of an intrinsic type, like double (whose implementation is supplied by the language), it wouldn’t actually be that bad to have even a direct dependency on it.
But as far as I understood from the C# manual page, the language allows also classes (i.e. user defined types) as constraints, and that would be bad. I’d have to investigate C# further, though, to be sure how the constraints in this language really work. In any case, thanks for your comments.
This is a side idea, but looking at the various examples (like sum) and my personal needs so far (i.e. the same function valid for all types of reals and/or integer) I would find types like real(*)
(which would mean any types of real), integer(*)
, complex(*)
and numerics(*)
(which would be real|integer|complex) very useful.
This could be obtained with PDT but I would have to redefine ALL intrinsic functions.
I have hinted at the possibility to support, in the future, through union types, exactly what you have in mind. See the paper’s section on “Type sets”, subsection “Present restrictions and possible future extensions”.
That is, in the future you should be able to do something like this:
function sum(x) result(s)
type(integer(*) | real(*)), intent(in) :: x(:)
typeof(x) :: s
integer :: i
s = typeof(x)(0)
do i = 1, size(x)
s = s + x(i)
end do
end function sum

y = softmax^(real, rank(x), 1, maxval, sum, exp, operator(-), operator(/))(x)
Thanks @everythingfunctional for providing an example here! I have many questions as I’m trying to grasp the details of the different proposals, but I’ll stay with the basic one:
Would this template approach require that the consumer code always instantiates also the internal operations as you show here with maxval, sum, exp, etc
.? In the same idea, I would have expected that at the consumer code level these declarations , softmax^(real, rank(x),
would not be required as they could be deduced from the input variable x
. I think that for some scenarios there are static parameter that could be allowed in this manner to give flexibily, but for this specific case, I would expect that the design enables disambiguation by extracting the characteristics from the input variables.
Thank you @everythingfunctional for taking the time to read our paper, and for providing your extensive list of notes. I’ll have to split my reply into two installments, both because this post with the bulk of my comments is going to get already very long, and because I am preparing for travel and a longer absence. My second post with the code examples that you requested may thus take longer.

Polymorphic objects with templated type-bound procedures effectively require run-time compilation. … The overhead would be huge, so performance terrible, and thus not very “Fortranic”.
I presume this is referring to our choice of providing parameterized (generic) methods, rather than parameterizing the interfaces/traits themselves. We had internal discussions on which of the two to prefer, and implementation considerations played a significant role in these discussions. We nevertheless decided to give parameterized methods a chance in a future LFortran prototype implementation (and to keep parameterized interfaces/traits as a fall-back option) because they significantly simplify user code (as it is shown in our paper).
We made this decision being aware of such methods having been implemented successfully in at least one mainstream language before, namely in Swift. This was sufficient practical proof for us, that parameterized methods can be implemented efficiently.
Not being a compiler developer, I do not know how this is actually accomplished in Swift. If @clattner_llvm is still following this discussion thread we all might get lucky, and get an answer to this question. I strongly doubt that he, and all the other Swift developers, would have chosen to implement parameterized methods, in particular in a language which is called Swift, if their performance was “terrible”, as it is theorized above. The proof is in the pudding. That is, in an actual implementation.

I don’t think it’s a good idea to mix OO type extension with traits, namely because how would an extension of an abstract type know all of the traits that it must implement, given that a declaration that a type implements a specific trait may be declared separately (even in a different module)? …
A significant number of language developers quite obviously disagrees with these statements. Type extension “mixed” (as it was called above) with interfaces (or protocols/traits) has been the main object-oriented programming paradigm since the 1990ies, namely in Objective C, Java, C#, D, etc., and more recently in Swift, which adds to these capabilities retroactive implementation of protocols.
As @clattner_llvm informed us up-thread, these features will also be supported in Mojo. Millions of programmers are using these features every day. So I’d recommend to everyone who is interested, to have a look into the documentation of these languages, and to try out these features for themselves using the compilers of these languages, in order to learn how all of this works in practice.
If one nevertheless doesn’t wish to go through the trouble of having to support such interoperability in Fortran, then there’s always the possibility to declare type extension obsolescent, and to have it replaced in the long-term by a pure traits based OO-model as it is supported in Go or Rust. This would simplify the language a lot. It would also not be the first time in Fortran’s history that a feature is declared obsolescent relatively shortly after its introduction (see the “forall” statement).

Data structures of runtime polymorphic trait objects requires a level of reflection/introspection likely to incur a large amount of overhead. The issue is that you don’t even know which v-table you have to use to look up the function until runtime. I.e. you have to determine which type the object is at run time, then determine which of the functions in that v-table corresponds to the related function from the trait. I think it is still an open question how often you need runtime polymorphism without inheritance, and whether it’s feasible to implement in Fortran.
None of these statements is valid.
Traits are contracts. As such, they enable easy conformance to the Liskov Substitution Principle (LSP, which is a form of design by contract). If an OO code conforms to this principle, then it doesn’t need to make use of any run-time type-inspections (RTTIs). So by using traits to express run-time polymorphism, one completely avoids RTTIs, and hence obtains run-time polymorphism of maximum performance.
The situation is reversed if implementation inheritance and inheritance hierarchies are used. In this case, violations of the LSP are essentially unavoidable. Which is the reason why one needs to use those pesky “select type” (RTTI) statements in Fortran, that drag down run-time polymorphism’s performance. So the above statements are wrong. The reverse is true: Traits improve polymorphic code performance!
The argument regarding v-tables is a poor one. In HPC codes, a trait object will be typically initialized only once (during the code’s initialization phase) at run-time, by calling the constructor of some class/type. Upon initialization, the constructor will automatically load the class’s v-table into the object, so that from then on the run-time system of the language can route any polymorphic calls to the functions of that class. This is hardly slower than static dispatch. It typically requires only some additional function pointer evaluation. There’s no reflection/introspection involved.
The “feasibility of implementation in Fortran” argument is equally poor. In an “apples to apples” (i.e. single to single, and multiple to multiple) inheritance comparison, interface inheritance is conceptually simpler, and hence easier to implement, than implementation inheritance.
C++ has multiple implementation inheritance, and it is well known how to implement this in compilers. Supporting multiple interface inheritance in Fortran will thus be even simpler than that.

It is not clear to me if/how the proposed traits allow the expression of relationships/operations between/involving multiple types? Consider the fully generic AXPY template (below) from recent examples/tutorials for templates. How would this be expressed/implemented with the traits proposal?
I will respond to this and your next item, using some actual code examples, in a separate later post – as already mentioned above.

Is it possible to address the situation where in certain contexts you want to use different implementations of certain traits for a given type? Consider the following example. …
See my reply to your previous item.

The type-sets feature prevents the use of third party types. Also, this feature is effectively already handled by the Japanese generic procedures proposal.
I presume what is meant by “third party types” is user-defined types (i.e. derived types in Fortran). Type sets, the way they are implemented in Go, accept also user-defined types. I’d recommend to read the link to Ian Lance Taylor’s work, that is cited in our paper, to learn which capabilities the Go developers intend to support through this feature in the future.
The statement that “this feature is effectively already handled by the Japanese generic procedures proposal” is of no relevance in the present context, because the cited Japanese proposal doesn’t address the other issues that are addressed in our paper.

For templated types, I find the scoping rules and correspondence between what is a parameter of the procedure and what is a parameter of the type hard to follow. Further, it’s not quite clear to me how type extension would work for templated types.
The syntax, that we employ, pretty much mimics that which is used by Go and Swift, and judging from almost all other reactions in this thread, Fortran users appear to find it quite easy to follow and to understand. Regarding the comment on type extension, I can only reiterate my recommendation to everyone interested in the topic to consult Swift’s documentation.

It’s unclear to me how exactly the correspondence between procedure arguments and template arguments is done for implicit instantiation.
I will refer back to my answer to the preceding item, noting that others in this thread, again, had no trouble.
It seems that many of the points, that I addressed above, stem from some general unfamiliarity with object-oriented programming languages or concepts, and some unexplainable, if not unbecoming, expectation towards the three of us to provide a document at the level of a technical specification, that contains even the most minute details of every single feature under consideration. What we decided to make kindly available here is a whitepaper, as it was correctly called up-thread.
Initially, this paper was intended for internal use, so one of its purposes still is to serve as a memo for ourselves, of the capabilities that are present in other programming languages. Some of these capabilities were already emphasized in an earlier thread here, along with a number of corresponding suggestions, that we made sure to follow, but which otherwise seem to have been completely forgotten!
I will finally add that we are excited that Ondrej Certik plans to prototype this entire proposal in an actual compiler, to iron out all the details, and ideally we’d like to have available more than one such compiler implementation.
PS: It seems that for some reason I can only cite two users in the same post, which garbled the initial formatting of this post. The admins might want to give this a look, as to why that happens.

It would also not be the first time in Fortran’s history that a feature is declared obsolescent relatively shortly after its introduction (see the “forall” statement).
That’s correct, but one has to consider how popular the feature effectively is, and how easy or difficult is it to change the codes that are already written with the feature.
I don’t think that forall
was often used, and most of time it’s quite easy to replace it with an OpenMP directive (I even suspect that the rise of OpenMP just killed forall
) or a do concurrent
, with minimal trouble. I’m not sure the situation is the same for abstract type extension.

Would this template approach require that the consumer code always instantiates also the internal operations as you show here with
maxval, sum, exp, etc
.?
At present, yes. We’ve occasionally discussed some ideas around automatic/inferred instantiation arguments, but so far haven’t found a good way of specifying exactly how and when that would occur. We would need to be able to specify precisely when they can’t be inferred to say in those cases the instantiation arguments must be provided.

I would have expected that at the consumer code level these declarations ,
softmax^(real, rank(x),
would not be required as they could be deduced from the input variablex
.

I would expect that the design enables disambiguation by extracting the characteristics from the input variables.
In specific examples this often seems intuitive, but in the general case type inference is a very difficult problem to solve, and one that Fortran compilers have not had to address before. We are partly hoping that compilers will be able to implement templates sooner if they are simpler.
@kkifonidis , thank you for the responses. I think this can be a very fruitful discussion. I do want to make sure it is clear what the decision the standards committee, and in particular the generics subgroup, has to make with respect to this proposal though. We can either continue to develop the design we have been working on for the past 4 years, get it into the F202Y standard, and hopefully have something broadly usable by the early to mid 2030’s, or we can switch to developing this proposal, for which there is definitely not time to get it into F202Y, and I don’t know if we could even have time to get it into the following revision. For now my opinion is still that he generics subgroup should continue down the current path and that future work can improve its design with respect to OO.

We nevertheless decided to give parameterized methods a chance in a future LFortran prototype implementation … because they significantly simplify user code

We made this decision being aware of such methods having been implemented successfully in at least one mainstream language before, namely in Swift. This was sufficient practical proof for us, that parameterized methods can be implemented efficiently.
This could be my lack of imagination in how they could be implemented, but my instinct is that not knowing what to instantiate until run-time makes it a very hard problem. As you say, “The proof is in the pudding.”

A significant number of language developers quite obviously disagrees with these statements. Type extension “mixed” with interfaces has been the main object-oriented programming paradigm since the 1990ies
Perhaps I didn’t word my comment and example well, but so far I’m not convinced it would be a good idea for Fortran. And perhaps I read more into this than was intended, but if you allow separate declaration of implementation and that complete implementation is not required for abstract derived types, you get into fundamentally unknowable problems, as illustrated by my example. Namely, that an extension type can’t know all of the traits that its parent type may be required to implement, and users of an abstract type then can’t be sure that all its child types actually have implemented the traits it wants to make use of. The right constraints could solve that problem, but I still think implementations might be tricky.

In HPC codes, a trait object will be typically initialized only once (during the code’s initialization phase) at run-time, by calling the constructor of some class/type.
This may again be my lack of understanding, but I don’t see how that’s possible. If a variable can change type at run-time, and thus needs to switch which implementation it’s using, how can it make use of a single, unchanging trait object?

I presume what is meant by “third party types” is user-defined types
I meant types that the trait didn’t/couldn’t have known about at the time it was written. I assumed that derived types could be included in a type set, but once the set is defined you can’t use it with any other type. This violates the Open-Closed Principle, open for extension but closed for modification. I’m not saying they’re never useful, but their use severely limits flexibility.

Fortran users appear to find it quite easy to follow and to understand
I’m a Fortran user, and the rules were not obvious to me. Maybe I just need to see more examples.

I will refer back to my answer to the preceding item, noting that others in this thread, again, had no trouble.
In many examples the “right answer” for inferred arguments seems pretty intuitive, but you have to be able to precisely write down the rules. Those rules weren’t obvious from the examples, but maybe we just need more examples.

It seems that many of the points, that I addressed above, stem from some general unfamiliarity with object-oriented programming languages or concepts,
I have plenty of experience with OO, but I think it is used far more often than it needs to or should be.

expectation towards the three of us to provide a document at the level of a technical specification, that contains even the most minute details of every single feature under consideration.
I didn’t mean to imply that you should have specified every detail in the paper you posted. But if this design were to go towards inclusion in the standard, all of those details do need to be specified. I just wanted to be clear about where I thought further work was still needed in the event that work continued.

one of its purposes … the capabilities that are present in other programming languages
In that regard this is good, and appreciated work. We did some of this early in the design of the current proposal, but not nearly as well documented, and hadn’t looked at Swift.

I’ll have to split my reply into two installments … My second post with the code examples
I’ll look forward to it.
@kkifonidis thanks for posting the answer and thanks @everythingfunctional for your reply.
Brad, for your first paragraph, my recommendation is the same that I shared on Monday at our generics subgroup call: finish the current J3 generics, but keep the door open for this OO-based extension.
I will do my best to prototype it in LFortran (I am hoping @meow464 and others can help), and hopefully Flang and other compilers could do the same. This will ensure the syntax/semantics is compatible with the current J3 generics in LFortran, and fix all the details in the proposal. I personally have no doubts that this can be implemented or the design amended appropriately to make everything work cleanly using strictly ahead-of-time compilation, no runtime compilation or reflection, and with high performance.
Also wanted to share that I am personally very excited about this, and thank you @kkifonidis for putting the hard work into this. The “right answer” for generics in Fortran lies somewhere in this design space covered by the function-based J3 generics and this OO-based proposal. We have made huge progress from “high-level ideas” into concrete proposals and implementations. Let’s keep pushing to figure out the rest.
I made a thread on zullip for discussing the implementation on lfortran https://lfortran.zulipchat.com/#narrow/stream/197339-general/topic/Traits.20proposal.20implementation
I’ve finally found an opportunity to post here my remaining replies to @everythingfunctional’s list of notes.
I’ll start by revisiting his original first two points, because I have a few more thoughts to share regarding these, and subsequently I will address his fourth and fifth points, that require code examples for illustration. I will then close with some (more) remarks on how type sets relate to the Open/Closed Principle.

- Polymorphic objects with templated type-bound procedures effectively require run-time compilation. …
Actually, they don’t. In fact, one of the points of using both a statically typed language (like Fortran) and type-checked generics (i.e. “strong concepts”) is to avoid such run-time compilation.
The above objection pretty much asserts that, e.g., the following code snippet that declares the interface of a generically parameterized method (a concept that we borrowed from the Swift language)
abstract interface :: ISum
function sum{INumeric :: T}(self,x) result(s)
deferred(self), intent(in) :: self
type(T), intent(in) :: x(:)
type(T) :: s
end function
end interface
is somehow semantically different from the following declaration of a generically parameterized interface/trait
abstract interface :: ISum{INumeric :: T}
function sum(self,x) result(s)
deferred(self), intent(in) :: self
type(T), intent(in) :: x(:)
type(T) :: s
end function
end interface
which is the more commonly used generics model, that is employed in e.g. Rust or Go.
In reality, these two forms are equivalent (also in seemingly more complicated cases, where e.g. multiple function signatures, or multiple generic parameters are involved). The first form can, in fact, simply be viewed as syntactic sugar, that allows one to shift to the compiler the burden of providing the boilerplate code that is required for instantiation and use of the second form (see Sect. 3.3.1 of our paper).
Hence, code that is written in terms of the first form could always be transformed by a compiler to make use of the second (e.g. through a transformation pass over a high-level intermediate representation). Compile-time monomorphization, to instantiate the generics of that latter form (as it is done in Rust), would then eliminate all the generic type parameters, and the rest of the lowering could then proceed as usual (e.g. to account for any remaining run-time polymorphism via v-tables).
Given that Fortran (like Rust) is a statically typed language, and given that our generics (like Rust’s) are fully type-checked, the compiler can obtain all of the information that is required for the above transformations from purely static program analysis – resulting in strictly ahead-of-time compilation.
Hence, the above objection is unfounded. It is likely, that there are also other, more elegant ways, to implement the gist of what I’ve sketched above. But I think the latter would be a perfectly viable way of implementing generic methods efficiently by a Fortran compiler.
Perhaps @certik can comment further on this.

- I don’t think it’s a good idea to mix OO type extension with traits, namely because how would an extension of an abstract type know all of the traits that it must implement, given that a declaration that a type implements a specific trait may be declared separately (even in a different module)? The following example attempts to demonstrate the problem with this, i.e. where the child type doesn’t know that it needs to implement some trait, and the program expects that it did, specifically wrt the statement from the end of Section 4.2.3.
We finally wish to remark that in case the “implementing” type is an abstract derived type, it must be allowed to provide an only partial implementation of the interfaces that it adopts. However, any non-abstract type that extends this abstract type through subclassing (i.e. implementation inheritance) must then provide a full implementation.
Example
I need to readdress this comment, because after I cross-checked in which section/context the quoted paragraph appeared in our paper, I noticed that an inconsistency had crept into our original manuscript, that required correction.
The above comment contains both a valid and an invalid point. The valid point is that abstract
derived types (in contrast to all other types) cannot be used together with the retroactive implementation capabilites of the implements
statement, for the reasons that were given in @everythingfunctional’s example. However, the assertion that this special (edge) case invalidates the entire “traits + type extension” paradigm doesn’t hold, as it was admitted by @everythingfunctional in one of his later comments.
There are two different ways in which abstract
derived types can, in principle, be handled within the framework of the new capabilities that we propose. Namely, by
-
prohibiting the use of
abstract
derived types with both theimplements
statement, and attribute. This would come closest to how the Swift language works, because the latter does not support abstract classes by design (as they are not truly required in a language that supports traits). This would also be the simplest solution to the issue. However, sinceabstract
types are already a part of Fortran, we felt that this option was a bit too restrictive, given that there is also the following possibility of -
prohibiting the use of
abstract
derived types only with theimplements
statement, but allowing their use with theimplements
attribute. The latter attribute naturally lacks retroactive implementation capabilities, and can therefore be made to be fully interoperable withabstract
types, in much the same way as Java’simplements
keyword works. It was towards these interoperability capabilities of theimplements
attribute that our above quoted paragraph was aimed.
The inconsistency in our original manuscript was that while the text that discussed the implements
statement correctly mentioned that this statement does not accept deferred
type-bound procedures (which in turn implies that it does not support abstract
derived types), this same text was also hosting the above quoted paragraph that should have appeared in the section that discusses the implements
attribute.
We have modified the corresponding sections of the paper to make this difference between the implements
statement and attribute clear, and to discuss how it relates to interoperability with abstract
derived types. We thank @everythingfunctional, for noticing the original inconsistency.
NB: Those of you who are involved in compiler implementation work that is connected to this proposal, should periodically check back on the proposal’s Github page to always download the latest version of the document, as we’ll keep updating it along the way.

- It is not clear to me if/how the proposed traits allow the expression of relationships/operations between/involving multiple types? Consider the fully generic AXPY template (below) from recent examples/tutorials for templates. How would this be expressed/implemented with the traits proposal?
Generic AXPY
First of all, I have to state that I found the provided Generic AXPY code example incredibly convoluted, and therefore extremely hard to follow, in particular given the relatively simple task that it is meant to accomplish. Personally, I’d forego the use of any new language features that would require me to write such convoluted code.
In the traits based design, this example can simply be written as follows:
program main
abstract interface :: INumeric
integer(*) | real(*) | complex(*)
end interface
real(kind(1.0)) :: a
integer :: x(10)
real(kind(1.d0)) :: y(10)
print *, axpy(a,x,y)
contains
function axpy{INumeric :: T,U,V}(a,x,y) result(res)
type(T), intent(in) :: a
type(U), contiguous, intent(in) :: x(:)
type(V), intent(in) :: y(size(x))
type(V) :: res(size(x))
res = a*x + y
end function
end program
Function axpy
would then work with any combination of the available intrinsic numeric types, which I believe was the actual intention here.
The above implementation also captures what the original code example intends to accomplish type-wise, namely to constrain the result of function axpy
(which is called res
above), to be of the same type as argument y
, while allowing for the types of arguments a
and x
to differ among both themselves, and that of argument y
.
Usage of the same type for variables res
and y
is enforced by employing the same generic type parameter, V
, for the declarations of these two variables. Accordingly, to account for possible differences in the types of all the function arguments, all of these arguments are declared by means of different type parameters (T
, U
, V
, which, in this simple example, all individually implement the functionality that is prescribed by the INumeric
interface; in more complicated cases one might have to use more than one interface to constrain the involved type parameters).
In the above traits based version, and as long as the involved types are intrinsic numeric types, there’s no need to muck around with specifying the required binary operators. Because this is already implicitly taken care of through the semantics of the type set interface definition.
Also, Fortran knows how to implicitly cast between these types to perform the required arithmetic. So, it’s sufficient to simply write res = a*x + y
to express the result of the arithmetic operations. Alternatively, one could use explicit casts, like so:
res = V(a)*V(x) + y
.
Of course, things would get more complicated if one would have to specify any interfaces explicitly, for instance to make the above code work also with any potential derived types.
But this only goes to show that our traits based design makes use of the principle of progressive disclosure of complexity. That is, simple things can be done simply, and only for complex tasks one has to introduce some actual complexity.

- Is it possible to address the situation where in certain contexts you want to use different implementations of certain traits for a given type? Consider the following example.
Differently Reduceable Integers
The way it is formulated, this question appears to contain a misunderstanding of the way traits based polymorphism works.
A given concrete type, like integer
, (i.e. a type that is not a trait itself, but implements a trait) is always tied to some single, concrete, implementation. Hence, such a concrete type by itself cannot possibly support multiple implementations of a trait, or polymorphism for that matter.
Consider the provided “Differently Reduceable Integers” example, and the combine
method that it implements for the integer
intrinsic type.
The first implements
statement assigns to this method an implementation of operator(+)
. While immediately thereafter, the second implements
statement attempts to assign to it an implementation of operator(*)
. This would be invalid code, because the second implements
statement would attempt to re-declare the first one.
It couldn’t be treated any other way by a compiler, because attempting to extract polymorphic behavior out of a single concrete type/implementation (in this case the integer
type) is not feasible.
Of course, there’s a way to implement in a traits based language what the original code example had in mind – by coding two different types that implement the same trait, so that instances of either one of these types could then be assigned to a polymorphic variable.
This also means that, in the considered example, exclusive reliance on some intrinsic type(s) won’t be sufficient, given that the language precludes the programmer from defining new or multiple such types. However, it is possible to use two different derived types to overcome this limitation, and achieve the code reuse for function reduce
that the original code example is after. See the following, fully worked out, example:
module reduction
implicit none
abstract interface :: IReduceable
function combine(self, other) result(res)
deferred(self), intent(in) :: self, other
deferred(self) :: res
end function
function identity() result(id)
deferred(id) :: id
end function
end interface
type, sealed :: SumReduceable
integer :: n
end type
type, sealed :: ProdReduceable
integer :: n
end type
implements IReduceable :: SumReduceable
procedure :: combine => sum
procedure, nopass :: identity => id_add
end implements
implements IReduceable :: ProdReduceable
procedure :: combine => prod
procedure, nopass :: identity => id_mult
end implements
contains
function sum(self,other) result(res)
type(SumReduceable), intent(in) :: self, other
type(SumReduceable) :: res
res%n = self%n + other%n
end function
function id_add() result(id)
type(SumReduceable) :: id
id%n = 0
end function
function prod(self,other) result(res)
type(ProdReduceable), intent(in) :: self, other
type(ProdReduceable) :: res
res%n = self%n * other%n
end function
function id_mult() result(id)
type(ProdReduceable) :: id
id%n = 1
end function
end module
program main
use reduction, only: IReduceable, SumReduceable, ProdReduceable
implicit none
integer :: n
type(SumReduceable) :: sum
type(ProdReduceable) :: prod
! call the polymorphic reduce function
sum = reduce( [(SumReduceable(n),n=1,4)] ) ! sum%n is now 10
prod = reduce( [(ProdReduceable(n),n=1,4)] ) ! prod%n is now 24
contains
function reduce{IReduceable :: T}(arr) result(res)
type(T) :: arr(:)
type(T) :: res
integer :: i
res = res%identity()
do i = 1, size(arr)
res = res%combine(arr(i))
end do
end function
end program

I assumed that derived types could be included in a type set, but once the set is defined you can’t use it with any other type. This violates the Open-Closed Principle, open for extension but closed for modification. I’m not saying they’re never useful, but their use severely limits flexibility.
I obviously disagree with the statement that the use of type sets severely limits flexibility. It was already discussed up-thread that the massive improvements in code conciseness (see also my version of the AXPY example), that type sets enable via the elegant expression of generics constraints, come at the cost of possibly having to change a type set interface down the road (if, in the future, one would like to admit new types in user code).
Such a change, to an already defined type set interface, can then trigger a recompilation cascade. But this will typically be an only minor inconvenience. The truly important point is that actual implementation code, that depends on such an interface, will continue to work without requiring any changes. That is, proper modification of type set interfaces will not contribute to code fragility, as I already elaborated on here:

Assume you start off with the need to use this function with only one type, say the
real
type. Then you would code interfaceINumeric
as follows:abstract interface :: INumeric real end interface INumeric
Now suppose that somewhat later you decide that you want to use this function together with all the
real
, and also with all thecomplex
kinds, that your compiler supports. The only thing that you need to change then is the definition ofINumeric
, namely as follows:abstract interface :: INumeric real(*) | complex(*) end interface INumeric
Your sum function will then work with both these types and with all their kinds.
Whether one nevertheless chooses to view the above as a violation of the Open/Closed Principle (OCP) depends on whether one has a “glass-half-empty” or a “glass-half-full” mentality. If anything, this is an only weak violation of the OCP, that will be perfectly acceptable in very many practical cases, especially if the need for addition of new types will be a relatively rare occurrence.
If it is strict conformance to the OCP that one requires, then the traits based design will, of course, also allow one to conform to such a requirement – by always providing the procedure signatures of interfaces explicitly, and then implementing these interfaces for any type that one wishes to use them with.