Traits, Generics, and modern-day OO for Fortran

Oh, your example was also missing typealias Element = U from VectorStruct required to get it to compile, could be that? I added that in my version

1 Like

Possibly, the protocol by @kkifonidis does not have “mutating”, while that by @zedthree has “mutating”? (according to the error message and the code in the Compiler explorer)

1 Like

Thank you @septc. If one adds mutating to the protocol then the compiler accepts it.

2 Likes

If we just assume that “mutability” (of the receiver object like self) is not an implementation detail and so should be included in the abstract interface, while not specifying the type name explicitly (like in the case of Rust/Swift/Fortran below), maybe another option is to use some placeholder keyword for declaration of the receiver object …? (or possibly, adding some optional clause like subroutine append(item) receiver(inout) etc in a way similar to “mutating”…? If not attached, it just means no intent on “self”.)

   abstract interface :: IAppendable
      typedef, deferred :: Element
      subroutine append(item) receiver(inout)  !! add properties of implicit self in an optional clause
      !! subroutine append(item) self(inout)  !! a shorter keyword
      !! subroutine append(self, item)
      !!   receiver, intent(inout) :: self   !! declare self explicitly but no type/class name
         type(Element), intent(in) :: item
      end subroutine append
   end interface IAppendable

I wouldn’t say “unfortunate”. Just different.

Since in Fortran you cannot invoke TBPs of a type or constructor, static methods don’t make sense anyway, and module-level procedures should be used instead.

I know I’m biased (since I love Go), but instead of “poorly designed mess” I would say “intentional minimalism” (Ken Thompson, Rob Pike and the other guy, initially bonded on how much they hated most of C++ features, so they went in a different direction when designing Go).

Go’s minimalist approach is compensated by its huge standard library —which, btw, makes extensive use of interfaces.

And Go also lacks static methods. Functions at the package-level must be used instead.

3 Likes

I will try to summarize what I think we learned from our recent exercise.

The Swift compiler does allow one to use a single protocol in the above example, as long as one adds the mutating keyword to the protocol (as it was noticed by @zedthree and @septc).

My apologies to the Swift developers for having drawn a premature conclusion regarding this point. However, the fact that this keyword is required in the protocol itself still implies some knowledge by the protocol about the types that are going to (potentially) implement it.

Hence, the last two of my above-listed questions still stand, and with them the assessment that some languages do a cleaner job of separating implementation details from interfaces than others.

What we are seeing here, in particular regarding the presence of receiver objects in traits, is a continuation of the old philosophical divide between the Simula 67 and C++ influenced OO languages on the one hand, and the Smalltalk influenced ones (Smalltalk, Objective-C, Go) on the other.

The latter languages are (historically) known for their effort to cleanly separate interfaces (and messages) from implementations, while the former ones aren’t. The idea of protocols (and protocol inheritance, on which today’s traits are based) originated organically in the Smalltalk influenced languages, and was only later adopted by some of the Simula 67 influenced ones, which I think led to the minor inconsistencies that we now occasionally observe.

Go’s co-developer Robert Griesemer stated in this talk that Go’s interfaces are a translation, into a statically typed language, of Smalltalk’s way to do messaging. I think this is the very reason why Go, despite making use of explicitly passed receivers in implementations, was not misled into having the receivers appear also within interfaces. Go’s developers had a clear model in mind of how to do messaging cleanly (namely the way Smalltalk and Objective-C do it).

Hence, we’d better be looking into all these latter languages for guidance. This is why our design is fundamentally based on Go’s model to formulate its traits (see also our new Go version of the vector example in our Github repo).

Time permitting, I will further elaborate (with examples, in a later post) on the troubles and logical inconsistencies that pop up if one chooses to deviate from this model when designing a traits feature for Fortran – that, importantly, needs to include a facility for implementing traits by intrinsic types.

6 Likes

This is a first out of two posts that elaborate, with examples, on the undesirability of receiver arguments within Fortran traits.

Let’s start with a summary of some basic requirements on a reasonably designed traits facility for Fortran. It should allow one to implement traits

  1. by derived types that are extensible,
  2. by derived types that are inextensible (i.e. sealed), but also
  3. by intrinsic types.

Now let us see what would happen, regarding the above three points, if we’d use the present language’s mechanism (that requires one to declare receiver objects in abstract interfaces using the class specifier) for the purpose of formulating Fortran traits. Here’s how such a trait would look like:

abstract interface :: IAddition
   subroutine add_to(self,arr)
      class(IAddition), intent(in)    :: self
      real,             intent(inout) :: arr(:)
   end subroutine
end interface

It declares the receiver argument of an abstract method as a run-time polymorphic variable whose (declared, or base) type is that of the trait. An implementation of this abstract method, bound to an implementing derived type that is named Adder, would then take a familiar form:

subroutine add_to(self,arr)
   class(Adder), intent(in)    :: self
   real,         intent(inout) :: arr(:)
   arr = arr + self%a
end subroutine

(with self%a being some unspecified data).

Of note here, is that the duo of declarations class(IAddition) in the interface, and class(Adder) in the implementation, would be type compatible (given that both are run-time polymorphic declarations [of class kind], and Adder would implement IAddition). Hence, we would fulfill the requirement listed in Item 1.

So far, so good. But what happens if the Adder type is made inextensible, i.e. sealed? In this case, the declaration of the receiver object in the method’s implementation would change. That is, the above case would become:

subroutine add_to(self,arr)
   type(Adder), intent(in)    :: self
   real,        intent(inout) :: arr(:)
   arr = arr + self%a
end subroutine

Here’s where the difficulties start, because now we have a self instance (in the interface) that is declared as a run-time polymorphic variable, and another self instance (in the implemention) that is not.

When overriding abstract methods, the Fortran standard views argument declarations like class(IAddition) that are overriden by declarations like type(Adder) to be mutually type incompatible – even if Adder is a descendant of IAddition (as it is the case in the present example). This holds at least for procedure arguments that are not passed-object dummy arguments.

For passed-object dummy arguments, the standard is vague. At best, one could say that for such arguments the mutual compatibility or incompatibility of the aforementioned type declarations is presently undefined.

When trying to incorporate also intrinsic types, like integer, into the overall design, the implementation of our abstract method would again be formulated in terms of the type specifier for object self:

subroutine add_to(self,arr)
   type(integer), intent(in)    :: self
   real,          intent(inout) :: arr(:)
   arr = arr + real(self)
end subroutine

Hence, we would face the same problem of undefined behavior occurrence as above. If, instead, we would attempt to implement the method as follows (similar to what we did in our first example above of an add_to implementation)

subroutine add_to(self,arr)
   class(integer), intent(in)    :: self
   real,           intent(inout) :: arr(:)
   arr = arr + real(self)
end subroutine

we’d face another issue: the class declaration specifier not being defined for any intrinsic types, including integers, because of its semantics requiring dynamic dispatch of methods – which is incompatible with intrinsic types.

To summarize, expressing the declarations of receivers in traits in terms of the class specifier (as it is required for unnamed abstract interfaces by the present language), would force us to either face logical contradictions (when dealing with intrinsic types, as in the last example), or to come up with complex type compatibility rules in order to overcome undefined behavior for passed-object dummy arguments. Rules that, moreover, would have to run counter to the rules that the language uses for all other procedure arguments.

This seems hardly worthwhile. The present language’s declaration mechanism for abstract interfaces is too much geared towards use by implementation inheritance and run-time polymorphism, to be a good fit for a generalization towards traits. It appears, for instance, wrong to have the class specifier sport that prominently in traits, given that traits are meant to equally support both run-time and compile-time polymorphism.

The approach that is used in the Rust language, to fulfill the latter requirement, is to not rely on any base types, or ancestral relations between types, when declaring receiver arguments within traits. Instead, receivers are of a Self type. That is, of a type alias, that can match all the (different) types that may implement a trait.

This leads us to the use of associated types for declaring receiver arguments within traits. In a subsequent post, I will argue that even this is undesirable and, moreover, entirely superfluous.

1 Like

In this second post on the undesirability of receiver arguments within Fortran traits, we’ll see how one could employ associated types to declare such arguments in a trait, in order to match the three different implementation examples of the add_to function that I gave in the first such post.

Recall, that the receiver declarations of these functions were the following:

class(Adder),  intent(in) :: self
type(Adder),   intent(in) :: self
type(integer), intent(in) :: self

Due to Fortran’s idiosyncrasy of requiring (in general) type or class specifiers to formulate variable declarations, a simple type alias (like Rust’s Self, that would merely match the implementing type) isn’t sufficient to match all of the above declarations from within a trait. One rather needs to come up with a mechanism that can match also the different type specifiers.

In an earlier iteration of our design, this was accomplished through the introduction of a new deferred specifier that expressed associated type declarations within traits. This specifier was provided with a variable’s name in order to let the compiler infer the complete declaration of that variable from an actual implementation of that trait.

That is, one wrote the trait in question as

abstract interface :: IAddition
   subroutine add_to(self,arr)
      deferred(self), intent(in)    :: self
      real,           intent(inout) :: arr(:)
   end subroutine
end interface

with the compiler then expanding deferred(self) to match any of the three above type declarations for self, including their specifiers. This appears like a satisfactory solution to the problems that were mentioned in my last post (although it introduces significant verbosity that is entirely avoidable; see the ultimate solution that is discussed below). Why then did we not ultimately stick to this design for our Fortran traits?

The main problem with this approach is that the presence of associated types pretty much “taints” a trait for use by run-time polymorphism, and effectively destines it for use by compile-time polymorphism. Such traits can only be made to work with run-time polymorphism if some form of (automatic) type erasure is supported by a compiler. This is, e.g., one of the things that Rust’s dyn Trait and Swift’s any Trait declarations accomplish.

Receiver arguments within traits, that are declared in terms of associated types, would therefore impose compile-time polymorphism on the vast majority of traits for use in the language (namely those that contain receiver arguments) – including traits that the programmer would wish to use to achieve run-time polymorphism. The programmer could only opt out of this dictate if the language would also offer him declarations with a type erasure capability.

We consider this to be a poor approach. Rather, our design philosophy is

  • to not bias Fortran’s traits facility in favor of one type of polymorphism over the other,

  • to not make run-time polymorphism any harder to use than compile-time polymorphism, and

  • to not burden prototype implementations of our traits with the requirement of having to implement type erasure in a compiler from the very beginning.

Don’t get me wrong. We will support type erasure for Fortran’s class(Trait) (similar to Swift’s any Trait) declarations for all the run-time polymorphic use cases involving associated types where this is truly required. But receivers within traits is not one of them.

We also wish to be able to introduce such support in an incremental manner during the development of the LFortran compiler (as it was the case during the development of the Swift compiler), which would be impossible with the above approach. Such incremental development is also the reason why, in our compiler prototype, we will initially allow traits with associated types to merely serve as generics constraints, and to relax this restriction only later on.

Now that I’ve outlined all of the problems, in two long posts, what is their actual solution? The solution is simple. It is to realize that all these troubles are entirely artificial, being caused by superfluous declarations of receiver arguments within traits. With the abolishment of receivers from traits, these problems disappear all at once (thereby confirming the soundness of the underlying reasoning).

Indeed, the vast majority of OO languages that support polymorphic interfaces/protocols/traits (namely Objective-C, Java, C#, Kotlin, D, Swift, Go, etc.) seem to get this right: they do not include receiver declarations in their polymorphic interfaces.

Importantly, this appears to be a basic principle that should be followed. It is not simply the result of some coincidental implicit passing of receivers in these languages. At least one of these languages, namely Go, uses explicitly passed receivers for its method implementations, and still doesn’t allow receivers to appear in its traits/interfaces. This fact indicates that implicit receiver passing rather happens to fulfill this principle automatically, whereas with explicit receiver passing substantially more care is required.

This becomes more obvious if one considers also the fact that Go’s interfaces appear to be straightforward translations (into the framework of a statically typed language) of Smalltalk’s and Objective-C’s message selectors, i.e. the (by definition) receiver-less parts of messages.

1 Like

Now that I’ve covered the receivers, here are my replies to @zedthree’s remaining comments or suggestions.

Apparently, you’ve missed some of our examples that illustrate how that feature would be employed. With our present design, the only place where multiple init identifiers would be used is overloading within traits. Where the initializers, that these identifiers represent, can be clearly distinguished from their different interfaces.

Multiple implementations of these initializers would need to be named differently by the programmer, and the names of their implementations would then be used to overload the (common) init identifier, pretty similar to the present language, and not different from your suggestion below.

Thanks for this suggestion. I like it, because it is concise. We actually already considered it (or something very similar to it), but had ultimately decided against it in order to keep the syntax, that is used to prescribe operator and initializer signatures, as symmetric as possible (which necessitated the identifier init, in order to achieve full analogy to operator).

However, I think a case can be made that initializers are sufficiently special that the syntax should reflect this special status. Hence, I think your suggestion has merit, and I believe we will ultimately incorporate it into the design. Even though I cannot tell right now whether this will happen still within the prototyping phase, or thereafter.

This is the type of feedback we seek from the community.

I agree. I regard the := operator as a “nice to have” rather than a “must have”. It will be one of the things that we’ll implement last. The actual worth of the entire rest of our proposal would not be affected if this operator wouldn’t make it into the final product. Simply view it as being the icing on the cake.

The generally accepted definition (that is also used in our document) of a generic procedure or method is that it declares one or more own generic type parameters. That is, such a procedure or method must have its own generic type parameters list. (See for instance the documentations of Java, C#, or Swift.)

Any generic type parameters that are declared by the class that the method is bound to do not count in this respect. Even though a method also has access to these latter parameters.

This distinction exists because of the different instantiation requirements in both cases. True generic method parameters need to be instantiated based on calls of the procedure/method that declares them (by making use of the actual arguments or type parameters that are passed to this method at the call site).

Whereas generic class parameters are instantiated through instantiations of the class that a method is bound to – possibly (but not exclusively) through calls to this class’s constructor. These parameters thus belong to the class, and are therefore (and moreover) accessible by all its methods. Hence, it would be both wrong, misleading, and terribly wasteful to put them also into the generic type parameters list of any single method.

See how this is done, e.g., in Swift’s syntax, which is also how it is (correctly) expressed in our syntax.

I think I still need to address two more comments/questions:

The lookup mechanism is the same as Swift’s, and is required in order to be consistent with the overall design goal of not having self objects (i.e. the return objects of initializers), or associated types that are connected to them, appear within traits. Otherwise, the mere presence of an initializer signature in a trait would spoil the trait for use with run-time polymorphism (see above).

The latest version of our proposal includes static methods. See Sections 4.2.1 and 6.3 of our document, and especially Listing 6.6 for an example. What it does not allow for is to have the static attribute appear in procedure signatures of traits. We followed Java’s interfaces in this respect, which we think got this detail right.

My two cents: I think this design will need to be greatly simplified if it is to be ever incorporated into Fortran. Mainly because its target audience is scientists who want to write efficient codes. So although I find the work impressive, and I love the progress and I think it is very needed, I was a bit pessimistic to see that the recent update added more keywords and abstractions (as far as I understand), rather than remove it. I hope some kind of simplification is in plan for the future.

I also say that keeping in mind that currently most of advanced Fortran features are not usable since the compiler support is so buggy. Therefore I do not have any belief that a complicated trait system will ever be implemented.

Hence my question: is there a plan to have this initial development followed a simplification round, which would, say, cut the volume of the proposal by half?

3 Likes

I tend to agree. Fortran users are mostly not computer scientists or software engineers.

I’m sure that advanced OO features will be useful to write general purpose libraries such as the “stdlib”, but I’m also sure that for 99.9% of the end users the “auto-generic” (or whatever the final name) procedures will be THE long awaited solution.

3 Likes

I also agree, adding that, IMHO, the main issue with the proposal is that it depicts “non-fortranic” syntax for features that either are already in the language, or have been selected for the next revision, e.g.:

  • Structure constructor overloading already provide what the initial statement tries to do.
  • The auto-generic procedures in the next revision will cover what the sum types intend to do.
  • The (template) requirements in the next revision already accomplish part of what the traits propose, so extending the feature would be preferable.

I’ll make this one as short as possible:

  • Many years of disregarding the developments in other languages have made a major revision of Fortran (comparable in scope to Fortran 90 or Fortran 2003) unavoidable.

  • Our proposal shows a path towards such revision by providing modern-day, traits based, generics and OOP. Both are indispensable for the language to stay relevant.

  • If you would like us to cut these features in half, you need to state which of the two you want us to drop, so that we can have a meaningful discussion about the consequences of such action.

  • Simplicity requires that one is also ready to drop old troublesome features, like type-extension and abstract derived types, as I’ve proposed it up-thread, but found no excitement for this idea.

  • The present proposal is expressly intended to provide an alternative to the capabilities, syntax, and semantics of competing approaches (see our original announcement). So it is moot to hold this point against it.

  • All of the features that we added enable new capabilities. Any claims to the contrary are wrong.

  • The recent iteration added merely the static method attribute, and the := operator. These have absolutely no bearing on abstractions.

  • We have, of course, ranked (internally) the proposed features by implementation priority (from high to low), so some of them (like interoperability with type-extension) could be postponed or dropped. I can provide a list if anyone is interested.

5 Likes

@gronki and @PierU are criticising the proposal for being too complicated, but I didn’t see any concrete arguments for showing this.. Moreover, is it, in their opinion too complicated from the point of view of compiler developers or users? Seemed like @gronki fears for the first and @PierU for the last. @jwmwalrus gave some condensed examples, but at least I didn’t understand the issues. I have no idea how laborious this proposal is to bring to reality (that discussion would be nice too) but as a potential future user the proposal makes a lot of sense to me (very clear, rather than complicated). It may well be that there are some hidden complications that I do not understand, but then it would be nice to see a clear comparison of some example code written in some hypothetical next revision -style and with this proposal. Why is the proposed style more complicated?

@kkifonidis the document is very well written and informative. I bet it has taken a lot of effort, so thank you. I learnt a lot from it. I like how you refer to the modern inspiration languages. Maybe I’m too simple minded, but I think it would be great to have a summary table listing all the new features/keywords and some quick comments/bullets and the inspiration source/reference. Then one could quickly see the actual new stuff and where it is coming from.

5 Likes

@eelis Thank you for your comment.

I plan to split the document into two parts in the future (because it has become longer than we’d like it to be). One part will contain the introduction and the language survey, and the second part will focus entirely on the Fortran extensions.

That second part might get restructured, according to the feedback we have received here, to also reflect the implementation sequence, or priority of the proposed features (high, low, etc.), or to add the table that you suggested. But I’ll wait with this until @certik and team have moved on with the prototype implementation.

2 Likes

I think the only way to know for sure is to just do it. Which we plan in LFortran. I would encourage Flang and GFortran developers to also implement it.

We already implemented a subset of the committee’s generic proposal in LFortran and this inheritance-based proposal doesn’t seem fundamentally more complicated. We have to have solid OOP support anyway for Fortran, and this proposal just “cleans” up some rough edges, at least for the runtime part. And the compile-time part (generics) I think is quite similar to what we already implemented. Once we get it done, we can document the details of how one can implement it in a compiler, which would be useful for other compiler developers. However many other languages have already implemented almost everything in this proposal, so I don’t think there is anything new from the implementation perspective, we just have to do the work.

7 Likes

On my side, my concerns are inline with @themos comment: Traits, Generics, and modern-day OO for Fortran - #91 by themos