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)

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.

5 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