Traits, Generics, and modern-day OO for Fortran

Nice effort, kudos - the Fortran language development endeavor needs this.

But it’s way too long for me to study fully and to offer anything comprehensively constructive at this time.

One thing though that immediately caught my attention and which, in my “Fortran book,” is fundamentally wrong is to view the following as an “interface”:

   abstract interface :: INumeric
      integer(*) | real(*) | complex(*)
   end interface

A better term shall be entity over interface

If you have the time to check out the following Introduction to Go generics, then you’ll see that type sets are interfaces, in the very classical sense.

Note it’s entirely in the context of Fortran and its language standard the term “interface” becomes inappropriate

i think it’s not an issue of context, but of syntax (or lack thereof).

if Having a value is equivalent to having a function that returns said value, then an interface can represent both.

Since Fortran is purposely explicit, maybe a better approach would be something like:

type interface :: INumeric
    integer(*)
    real(*)
    complex(*)
end interface

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

This sounds quite handy. Thank you.

1 Like

I just want to note that I haven’t been ignoring this, but I am trying to find time to come up with examples and responses. Unfortunately that may not be until after the upcoming J3 meeting. Whilst you have made some good points and addressed at least one of my concerns, I think there are still some counter examples to be made.

One quick response wrt to the use of type-sets that I have thought of a new way to formulate. I don’t think they qualify as generic programming. Namely, rather than being a way of writing a generic algorithm, they instead are a shorthand for writing a set of specific implementations of that algorithm. Whilst it may be relatively easy, it does require modifying the existing code to extend it to new types.

3 Likes

I am happy to announce, that we have meanwhile revised our traits-based polymorphism design for Fortran, in order to refine it and to generalize it significantly, while making its syntax even more concise. The following list summarizes the changes:

  1. Passed-object dummy arguments were removed from traits. They are now only required to be provided in actual implementations (as in Go). This has obviated the need to use associated types for the declaration of such arguments.

  2. The deferred declaration specifier for associated types has been dropped in favor of declaring associated type names via typedef statements. This allows for the reuse of such names in a trait.

  3. A predefined associated type, itself, to refer to the implementing type, is available.

  4. The signatures of both ordinary procedures, operators, and initializers (i.e. constructors) for types are now all allowed to appear in traits.

  5. Overloaded versions of all these signatures can be specified as well.

  6. The implements statement, and the contains sections of derived types, now provide improved syntax to concisely implement all of the above items. Among other things, this adds type-bound initializers to Fortran.

  7. The previously proposed type casting functionality for generics has been extended. It now works regardless of whether the type to be cast to is language- or user-defined (a feature that was borrowed from Swift).

  8. Fortran’s present, valuable, restriction, of prohibiting its language-intrinsic operators from being overloaded for intrinsic types, can now be honored and enforced by a compiler.

  9. Structural subtyping (a la Go), to supplement the nominal subtyping (a la Swift and Rust) and to thus improve code conciseness even further (as it was done in Mojo), has been added as a candidate for future inclusion into the design.

Check out the newest, significantly updated, version of our document for discussions and illustrations of all these improvements, using revised examples of our Rust, Swift, and Fortran codes!

8 Likes

I am happy to announce the second update of our traits and polymorphism proposal for Fortran.

This update focuses on easing the parsing of our proposed Fortran extensions, and on aligning the design’s type inference capabilities and information hiding aspects with those of other modern languages. The following is a summary of all the changes:

  1. The syntax of generic parameter lists was slightly adjusted to preclude any parsing ambiguities, and to thereby ease the implementation of a parser for a prototype. For instance, trait combinations are now formulated in terms of a ‘+’ operator (as in Rust).

  2. As a further improvement to generic type parameter lists, the programmer is now allowed to omit the IAnyType trait as a(n explicit) constraint for generic type parameters. Such a type parameter’s conformance to the IAnyType trait will then be inferred by the compiler (as it is the case in Swift). We plan for further conciseness improvements to the present generics syntax after the realization of a first successful prototype implementation.

  3. Type inference was also enhanced by adopting the Go-like := assignment operator. This now enables simultaneous automatic declaration and initialization of local variables in Fortran, even amidst executable statements, and within loops!

    This feature complements the type inference capabilities of our generics, and will lead to significant improvements in Fortran code conciseness and flexibility – in both conventional and future REPL (read-evaluate-print-loop) usage of the language.

  4. Derived types now support static methods, i.e. methods that are bound to the type itself rather than its objects. These methods are always dispatched statically, and enable a clean implementation of type-bound operators. They are also required for some important future extensions.

  5. The previously proposed structure constructors, that featured initialization of private derived type components, were removed from the design to allow for some more extensive (re-)evaluation. The handling of both structure and user-defined constructors is now modeled closer to Swift’s initializers.

We believe that with this iteration we have converged on the set of features that should be included in a prototype implementation, and have therefore frozen this set, given that such an implementation has recently started in the LFortran compiler.

Check out our revised text, that now provides updated code examples which make consistent use of the type inference capabilities and information hiding aspects of the languages that we consider, including our new extensions for Fortran. For readers who are interested in actual implementation details of the employed generics, we now also provide references to the model that was used for their implementation in the Swift language.

12 Likes

This looks very nice! I think this syntax is for the most part very clean, and it would be a powerful addition to the language! I’ve not fully digested everything, but I have a few comments about various bits:

I know this is a bit of a distraction, but your Rust example is overly complicated, which might have impacted your conclusions from it. For instance, you say there’s no way to cast generic types without writing your own methods, but there’s Num::FromPrimitive in the Num crate you’re already using, which means zero new code needs to be written for Averager to work with f32, for example. You can also get away from using the Num crate entirely with two (admittedly quite long!) lines:

    pub trait INumeric: Default + Add<Output = Self> + AddAssign + Div<Output = Self> + Copy + From<u16> {}
    impl<T: Default + Add<Output = T> + AddAssign + Div<Output = T> + Copy + From<u16>> INumeric for T {}

These built-in traits are sufficient to get the example to work, using T::default() instead of T::new(0), and (x.len() as u16).into() to cast the slice length to T.

You can also very easily vastly simplify the creation of the averagers by moving the call to Box::new into the custom constructors, and relying on Rust’s powerful type inference to work out the types of avi, avf:

    let (avi, avf) = match key {
        1 => (Averager::new(SimpleSum {}), Averager::new(SimpleSum {})),
        2 => (
            Averager::new(PairwiseSum::new(SimpleSum {})),
            Averager::new(PairwiseSum::new(SimpleSum {})),
        ),
        _ => {
            println!("Case not implemented!");
            return;
        }
    };

Note that I don’t name i32 or f64 here at all – they’re inferred from the calls to avi.average(), no explicit instantiation needed.


It also seems like the reserved init function name isn’t really necessary, we already have a mechanism to specify constructors of types with interface TypeName. The problem with adding reserved names is that they will inevitably clash with existing uses. The lookup mechanism is a little strange to me too, needing to find the associated type based on the return type of the function.


I think there’s a big flaw in not requiring an explicit object argument in trait function signatures. You point to this being how it works in Swift, but in Swift no explicit self is required to access instance members. Fortran does require an explicit dummy argument for the instance, and so it should be included in the trait function signatures. Not requiring it makes it harder to a) look up the correct signature (either for a human or machine), and b) verify all the dummy argument attributes match. For instance, your definition of IAppendable in 5.1.3:

abstract interface :: IAppendable
  typedef, deferred :: Element
  subroutine append(item)
    type(Element), intent(in) :: item
  end subroutine append
end interface IAppendable

would be much clearer if it were:

abstract interface :: IAppendable
  typedef, deferred :: Element
  subroutine append(self, item)
    type(IAppendable), intent(inout) :: self
    type(Element), intent(in) :: item
  end subroutine append
end interface IAppendable

These are very different signatures, and I don’t really see the benefit from skipping the self argument in the signature.


It also seems inconsistent to have some generic procedures not require listing the generic types. For instance, you have the two generic procedures in different sections:

function average{INumeric :: T}(self,x) result(a)
  type(Averager), intent(in) :: self
  type(T), intent(in) :: x(:)
  type(T) :: a
  a = self%drv%sum(x) / T(size(x))
end function average

subroutine append(self, item)
  type(Vector{U}), intent(inout) :: self
  type(U), intent(in) :: item
  self%elements = [self%elements,item]
end subroutine append

Why doesn’t append need to be subroutine append{IAnyType :: U}(self, item)? It seems like the only way the compiler can work out that append is a generic procedure is by parsing the dummy arguments and seeing Vector{U}. Wouldn’t it be more consistent to require listing the generic types in the signature here too?


The type-inferring-assignment operator := is very nice, but I think you’re going to have to nail down a lot of formal specifics if it’s going to make any progress. For example, what scope is the name bound to, do constructs that aren’t currently scopes now become scopes:

do i := 1, 10
  j := 2 * i
end do
! Is i still valid here?
! Is j still valid here?

I can imagine this small feature alone potentially being quite controversial, so you may not want to bind it too closely to the rest of your proposal!

1 Like

Thank you for your feedback.

I’ll try to answer your questions by providing some insight into our thought process of designing the proposed features, since some of the more subtle points may not be entirely obvious to someone who was not involved in this process.

I’ll also comment only on those of your points that relate to the design of our Fortran extensions, since you have stated yourself that your other comments may be distracting, and because I do not wish to get involved into a Rust vs. Swift vs. Go language argument.

I personally think that the present mechanism to overload structure constructors in the language is needlessly verbose.

Much more importantly, it is also inadequate for being used together with traits, i.e. for formulating the requirement within a trait that an implementing type needs to provide an initializer/constructor with a certain signature.

How would you express such a requirement with the present syntax?

There’s a fundamental flaw in the present language. Not in our traits design. See below.

No, it shouldn’t. Please read our paper more carefully, in particular the footnote that addresses the point of explicit vs. implicit passed-object dummy arguments.

Fortran is by no means unique in that it requires explicit passed object dummy arguments. Both Go and Oberon-2 do the same (for those who don’t know it: Fortran’s OO design is largely based on Oberon-2, but it includes some mistakes that are not present in Wirth and Mössenböck’s original design).

In both Go and Oberon-2, passed-object dummy arguments (“receivers”) are syntactically clearly separated from message (method) signatures. Thus, Go interfaces also correctly do not contain passed-object dummy arguments, even though Go (like Fortran, and different from Swift) makes use of explicitly passed receivers.

This is fundamentally not a question of explicitly vs. implicitly passed receiver objects. It is a question of how to design traits (or message signatures) correctly so that they can be implemented (i.e. their messages received) by different types, more precisely by both user-defined and language-intrinsic types!

How then would you formulate a trait that is to be implemented for a language-intrinsic type?

The present language requires you to express the self argument in an abstract interface using the class, instead of the type, declaration specifier. But the class specifier is undefined for intrinsic types, because its semantics require dynamic dispatch of methods.

Hence, you also cannot formulate abstract interfaces in the present language that could be implemented by intrinsic types! As I already said, such non-generalizability is a fundamental design flaw of the present language.

You could come up with a different declaration specifier, that reduces to either class or type, for use in both cases, and this is indeed what we had in an earlier iteration of the design. But this makes traits needlessly verbose, and there’s absolutely no need for such complexity if the actual root of the problem (the provision of self objects in traits) is properly fixed.

You got it wrong. The append procedure that you quoted is not a generic procedure, because it does not contain a (curly braces) generic parameters list. It merely has access to the generic parameter, U, of the type, Vector{U}, that it is bound to.

Only procedures with a generic type parameters list (i.e. with curly braces immediately after the procedure’s name) are generic!

We will do exactly that. That will all be a part of the prototype implementation process.

1 Like

This is all quite impressive, but I have a word of caution. I was involved, decades ago, in a project with research-grade programming languages and type systems (https://research.ibm.com/publications/the-type-inference-and-coercion-facilities-in-the-scratchpad-ii-interpreter). The bitter lessons that I learned:

  1. There are very few people who can master the abstractions and use them effectively (roughly, the top 1% of academic applied-mathematicians and computer-scientists)
  2. The queue of edge cases needing clarification seemed to never end. This problem was hidden by the fact that only one implementation existed, and so became the definition of behaviour. A misty landscape.
  3. Language experts got bored (presumably) with the implementation chores and moved to other projects, leaving the implementation without expert support.
  4. Early adopters of the fancy features found it difficult to translate their insights to other environments and consequently their influence among their peers waned.
  5. Despite the promise, big breakthroughs were achieved by other attempts, some being heroic one-man efforts with a far more pedestrian programming language.
3 Likes

Thanks for your reply @kkifonidis.

Indeed, many things in Fortran are overly verbose! While it would definitely be nice to have a simplified syntax for constructors, I do think you have to be very wary about introducing new keywords that are going to clash with existing uses.

Another potential source of problems with init is having multiple type’s constructors in the same scope, all called init. I’m not sure there are any languages that resolve based on function return types. You already introduce a new keyword intitial inside type definitions, why not use that?

For example, something like:

abstract interface :: ICastable
  initial(n)
    integer, intent(in) :: n
  end intitial
end interface

type :: MyType
contains
  initial :: my_init
end interface

This might make it much easier to get initial into the language as almost pure syntactic sugar to expand to an interface block, rather than introducing (I have a feeling such syntax has been proposed before?)

I’m also not really convinced by your arguments about the implicit self dummy argument. Maybe I’m missing something, but intrinsic types don’t have type-bound procedures, so I’m not sure what procedures you would be able to declare in a trait? In fact, in section 5.1.3, you define a trait INumeric which has function operator(+) that does list all its arguments. Please could you give an example where having to include self in the signature would mean it wouldn’t work with intrinsic types?

You didn’t address my point about being able to distinguish between mutating and non-mutating methods. For example, it’s really quite important that append in IAppendable takes the instance by intent(inout), otherwise the function may still conform to the trait but be semantically wrong. Swift has the mutating keyword, Rust requires passing &mut self, both in the trait signature.
Similarly, with implicit self, it’s not possible to distinguish between virtual (pass) and static (nopass) procedures. Swift has the static keyword on the trait signature, and Rust requires explicit self. In your current proposal, how would you specify a trait has a static (nopass) method?

I don’t see how it isn’t a generic procedure. It’s generic over the type U, which is not a concrete type – that surely makes it generic by definition?

1 Like

The above paragraph contains numerous factual mistakes, and I think I also know why this is the case. The reason (as I’ve already tried to explain up-thread) is quite simple: Even some of the most modern languages (that support traits, like Rust, or the brilliantly designed Swift) occasionally miss to do a clean enough job of separating interfaces from implementation (details). The language whose design is cleanest in this respect is Go, which you have (unfortunately) completely ignored.

I am elaborating on this in more detail below. But first, here are some important basic facts:

  1. The pass attribute in Fortran is neither tantamount to, nor connected to, “virtuality”, i.e. dynamic binding or dispatch of a method. Neither is nopass tantamount to static dispatch. One can easily have nopass methods in Fortran that are dynamically dispatched, and one can have pass methods that are statically dispatched. I don’t know why none of the other Fortran OO programmers, or the compiler developers who read this thread, had the courtesy to point this out to you, during my absence. You can convince yourself of this fact either by consulting the standard, a good modern Fortran book, or by writing small OO test codes, which I won’t do here, because it would take up too much space, and would therefore needlessly distract.

  2. Similarly, mutating in Swift is not what you made it out to be. The mutating keyword for a method in Swift is only needed if one has to mutate (with this method) state that is stored within a struct. The reason for this need is that structs are value types in Swift! In contrast to classes, which are reference types. You can therefore easily get rid of every occurrence of mutating in Swift methods by binding them to classes rather than structs.

Consider our vector.swift example:

public protocol IAppendable {
    associatedtype Element
    mutating func append(_ item: Element)
}

struct Vector<U>: IAppendable {
    private var elements: [U]
    
    init(_ item: U) {
        self.elements = [item]
    }

    mutating func append(_ item: U) {
        self.elements.append(item)
    }

    func printout() {
        print(elements)
    }
}

var doubles = Vector(0.0)
doubles.append(1.5)
doubles.append(2.2)
doubles.printout()
    
var bools = Vector<Bool>(true)
bools.append(false)
bools.append(true)
bools.printout()

var strings = Vector("John")
strings.append("Mary")
strings.append("Anne")
strings.printout()

You can replace every occurrence of mutating in this code by switching from structs to classes, as follows:

public protocol IAppendable {
    associatedtype Element
    func append(_ item: Element)
}

class Vector<U>: IAppendable {
    private var elements: [U]
    
    init(_ item: U) {
        self.elements = [item]
    }

    func append(_ item: U) {
        self.elements.append(item)
    }

    func printout() {
        print(elements)
    }
}

var doubles = Vector(0.0)
doubles.append(1.5)
doubles.append(2.2)
doubles.printout()
    
var bools = Vector<Bool>(true)
bools.append(false)
bools.append(true)
bools.printout()

var strings = Vector("John")
strings.append("Mary")
strings.append("Anne")
strings.printout()

This latter example clearly accomplishes (without any use of the mutating keyword at all) what according to your above statement would be an impossibility (simply compile and run this code to convince yourself that what I am stating here is nothing but the pure facts).

Now consider what will happen if, for solving the same programing problem, we wish to code two implementations within the same program: one that is based on a struct, and one that is based on a class, but is otherwise identical. We’d like to avoid repeating ourselves as much as possible, so we’ll try to use the same protocol for these two implementations, as follows:

public protocol IAppendable {
    associatedtype Element
    func append(_ item: Element)
}

struct VectorStruct<U>: IAppendable {
    private var elements: [U]
    
    init(_ item: U) {
        self.elements = [item]
    }

    mutating func append(_ item: U) {
        self.elements.append(item)
    }

    func printout() {
        print(elements)
    }
}

class VectorClass<U>: IAppendable {
    private var elements: [U]
    
    init(_ item: U) {
        self.elements = [item]
    }

    func append(_ item: U) {
        self.elements.append(item)
    }

    func printout() {
        print(elements)
    }
}

If we try to compile this code, the Swift compiler will reject it, and force us to write two different protocols for use with the two different implementing types. One of these protocols, namely the one that is destined for implementation by the struct, will have to contain the mutating keyword. The other will not.

  • Why is this the case? Why can’t we use just a single protocol to send the same message to two different receiver objects?

  • Why does a protocol need to care about the actual object’s type that is going to implement said protocol?

  • Why does a protocol, an abstraction, have to care about any of the details, that concern (some of) the protocol’s possible receivers/implementations?

For the OO programmers among you: This is a (language-enforced!) violation of the Dependency Inversion Principle (“Abstractions should not depend upon details”), that makes no sense.

The answer is that all of this is a consequence of an unfortunate design glitch (i.e. inconsistency) in the Swift language.

The clean way to designing this would have been to require the presence of mutating merely in the signature of the implementing method of the struct. But to disallow it from appearing in the signature that is contained in the protocol (i.e. the abstraction).

The abstraction would then have been a true abstraction, and it would have been unique, and reusable. Whereas now it is neither of these three.

Similar reasoning applies to self (receiver) objects. They are details of actual implementations. (Because in order to formulate the implementations themselves, one may need to access the field objects or methods of a struct or a class from another of its methods. One may also not need to, in which case you should use nopass in Fortran.)

Receiver (self) objects should therefore not appear in signatures of protocols/interfaces/traits. Regardless of whether a language chooses to make them available to actual implementations in an explicit or implicit manner.

1 Like

Probably because this discussion (and the associated paper) is miles above the concerns of the average Fortran programmer on this forum. I’m reading it, but understanding hardly 20% of what is written :smiley: !! I have very basic needs in terms of OO, and what I’m waiting the most are rather the generic procedures. This is inline with @themos post above .

4 Likes

Same here, but I really admire the idea of understanding pros and cons of several languages, and bringing together the best features with a Fortran flavor :smiley:

3 Likes

Thanks for your comments @PierU and @ricriv.

I will do my best to answer all of @zedthree’s questions. But he brought up a lot of difficult (design related) topics, and I have to take them one at a time, because it takes a lot of effort to explain the underlying issues.

I hope my explanations have been clear enough so far.

5 Likes

Yes, this true, Fortran doesn’t have true static methods, which is unfortunate. I mistakenly conflated things here.

Frankly, I don’t know much about Go, except that even the people who love think it’s a poorly designed mess, so I’m not sure about the wisdom of drawing lessons from it.

Sorry, but I didn’t claim anything was impossible, I said that Swift uses mutating to indicate that a struct method mutates the instance. I don’t actually know enough about Swift to argue about its details.

This doesn’t appear to be the case, the compiler is perfectly happy with just the one protocol: Compiler Explorer
so I have to respectfully disagree with your conclusions from this example.

I do agree, however, that this is a strange inconsistency between struct and class.

I also respectfully disagree that this is an implementation detail. Again, in the IAppendable example, it’s important semantic information whether or not the instance is intent(in) or intent(inout).

In C++, it’s possible to overload on the const-ness of the method, so overriding virtual methods are required to match the const-ness of the base class, for example:

// Abstract base class with pure virtual method, somewhat similar to a trait
struct Base {
  virtual void foo() const = 0;
};

struct Derived: Base {
  void foo() const override {}
};

Dropping the const from Derived::foo is a compiler error. This isn’t an implementation detail, void foo() const and void foo() are two different methods.

Another example where the mutability of the instance is important semantic information is sort: being able to see at a glance from the trait whether or not this method should mutate the instance is really important information for developers. If you saw mutating sort() in Swift, sort(&mut self) in Rust, or intent(inout) in Fortran, you would instantly know that it was an in-place sort rather than returning a sorted copy.

1 Like

Just quickly, here’s what I get with a recent Swift version (6.1.1):

vectortest.swift:6:8: error: type 'VectorStruct<U>' does not conform to protocol 'IAppendable'
 1 | public protocol IAppendable {
 2 |     associatedtype Element
   |                    `- note: protocol requires nested type 'Element'
 3 |     func append(_ item: Element)
 4 | }
 5 | 
 6 | struct VectorStruct<U>: IAppendable {
   |        |- error: type 'VectorStruct<U>' does not conform to protocol 'IAppendable'
   |        `- note: add stubs for conformance
 7 |     private var elements: [U]
 8 |

Weird, the compiler explorer has Swift 6.1:

Is this a difference between Swift 6.1 and Swift 6.1.1?

I haven’t run version 6.1 myself, so I can’t tell.

1 Like