Override keyword for inheritance

When using inheritance in Fortran, I often make a mistake/bug (*1) by not correctly updating the name of methods (= TBP) in a subtype even when I change the corresponding method names in a base/super type. To prevent this kind of error, other languages seem to provide the override keyword (please see below for the example of C++, C#, Swift, and Kotlin). Because the mismatch of method names can lead to silent bugs, I believe the override keyword (when attached on the subtype side) would be very useful, so I hope it will be included into future standards. (*2)

(*1) I already experienced this type of bugs 4-5 times (including today …).

(*2) This topic might have a similar thread already on the Github “fortran_proposal” site. In that case I am sorry for a redundant thread.)

C++
https://en.cppreference.com/w/cpp/language/override
C#
https://docs.microsoft.com/en-us/dotnet/csharp/language-reference/keywords/override
Swift
https://docs.swift.org/swift-book/LanguageGuide/Inheritance.html
Kotlin
https://kotlinlang.org/docs/inheritance.html#overriding-methods
D
https://dlang.org/spec/attribute.html#override
Chapel
https://chapel-lang.org/docs/language/spec/classes.html#overriding-base-class-methods

1 Like

Can you show a short Fortran example? Isn’t this what deferred procedures are for?

In my understanding, no, I think whether methods are deferred or not is not important here; the problem is that subtype methods could be given wrong names (inadvertently) by the user, which fails to override the intended method of the super type.

I will try to gather some related things, and the explanation in the “Overriding” section of the above Swift page may be useful (there seem to be several reasons that various languages introduce this keyword, not limited to my “use (bug) cases”).

To override a characteristic that would otherwise be inherited, you prefix your overriding definition with the override keyword. Doing so clarifies that you intend to provide an override and haven’t provided a matching definition by mistake. Overriding by accident can cause unexpected behavior, and any overrides without the override keyword are diagnosed as an error when your code is compiled.

The override keyword also prompts the Swift compiler to check that your overriding class’s superclass (or one of its parents) has a declaration that matches the one you provided for the override. This check ensures that your overriding definition is correct.

2 Likes

I see the problem. Here is a naive example:

module parent_mod

  implicit none

  type :: parent
  contains
    procedure :: say_hello
  end type

contains

  subroutine say_hello(self)
    class(parent), intent(in) :: self
    print *, "Hello from parent"
  end subroutine
end module

module child_mod

  use parent_mod
  implicit none

  type, extends(parent) :: child
  contains
    procedure :: sayhello ! inadvertent name error
! here we would want an override attribute to force
! an error for name mismatches or wrong interfaces
  end type

contains

  subroutine sayhello(self)
    class(child), intent(in) :: self
    print *, "Hello from child"
  end subroutine

end module

program main

  use child_mod

  type(child) :: foo

  call foo%say_hello() ! calls parent method
end program
1 Like

Exactly :sunflower: It might appear very rare to make such a mistake, but while doing “code refactoring”, I sometimes failed to update all the names in all the subtypes, which led to silent bugs (fortunately, I noticed the error rather soon from the output, but I am afraid it is not always possible to notice the mistake so easily).

Given that Fortran has the non_overridable attribute to make sure a procedure is not overriden, it sounds very reasonable to have an attribute called override (or overriden) to indicate a procedure must have been overriden. This attribute would only be allowed in derived types that are extended from base types.

1 Like

OP may want to clarify and make clear the issue of interest but the problem is likely different than what is discussed thus far and the matter may be one that compiler implementations can step in to help practitioners.

Going back to the point in the original post, it is highly likely most folks who can vote toward changes toward the standard will hesitate to support an addition in the form of an override clause. For the language already requires a binding-name => specific-bound-procedure syntax to achieve the overriding:

  type, extends(parent) :: child
  contains
    procedure :: say_hello => sayhello !<-- specific "sayhello" overrides "say_hello" binding of parent

An override attempt without such syntax will force the compiler as-is to issue a diagnostic per the other constraints in the standard. Thus any added enforcement such as with override clause appears unnecessary, especially for a highly resource-constrained ecosystem of Fortran.

On the other hand, the root of the issue mentioned in the original post likely has more to do with a) Fortran allows both the short-hand syntax where the binding-name can be omitted in which case it is considered the same as the specific procedure and b) the language also allows an explicit specification where the binding-name can be the same as the specific bound procedure, a silly situation like so:

    procedure :: sayhello => sayhello

Practitioners then to take advantage of the shortcut in a) above and on rare occasions, they might have typos leading to the case in b) above.

Rather than an override keyword now (Fortran 2003 could have introduced it but it didn’t), the pedantic modes of compilers can alert users - when they so choose to employ the option - on the situations where the binding-name is the same as the specific bound-procedure. Users should run their codes with such modes whenever they author new or refactor existing codes and that should alert them to the potential problems.

1 Like

So to complete the point on this, the Fortran standard on many matters, especially with support toward object-oriented programming, has effectively embraced both verbosity as well as pedantism already. And the suggested type declarations in the language standard to avoid the kind of problem mentioned in the original post is like so: note the binding-name => specific-bound-procedure syntax.

module parent_mod

  implicit none

  type :: parent
  contains
    procedure :: say_hello => parent_says_hello
  end type

contains

  subroutine parent_says_hello(self)
    class(parent), intent(in) :: self
    print *, "Hello from parent"
  end subroutine
end module

module child_mod

  use parent_mod
  implicit none

  type, extends(parent) :: child
  contains
    procedure :: say_hello => child_says_hello
  end type

contains

  subroutine child_says_hello(self)
    class(child), intent(in) :: self
    print *, "Hello from child"
  end subroutine

end module

program main

  use child_mod

  type(child) :: foo

  call foo%say_hello()
end program

C:\Temp>gfortran p.f90 -o p.exe

C:\Temp>p.exe
Hello from child

C:\Temp>

But then additional verbosity on top of the existing situation, particularly if that leads to more required work and thus cost for compiler implementations, is likely going to be unwelcome.

1 Like