Overriding type-bound procedures with different dummy arguments

In Python, one can freely override methods inherited from parent classes without any constrains on the arguments, as illustrated below for __init__ (edit: __init__ was an unfortunate choice; just imagine an arbitrary method/procedure):

class Parent:
    def __init__(self, a):
        self.a = a

class Child(Parent):
    def __init__(self, a, b):
        super().__init__(a)
        self.b = b

kid = Child(1, 2)

I tried doing something similar in Fortran, but it seems that normal procedure overriding requires that “both bindings must have the same number of dummy arguments”. After some googling, it seems that one must use generic binding, more or less like so:

module supe
   implicit none
   private
   public :: parent, child

   type :: parent
      integer :: a
   contains
      procedure, pass(self) :: parent_init
      generic :: init => parent_init  !?
   end type

   type, extends(parent) :: child
      integer :: b
   contains
      procedure, pass(self) :: child_init
      generic :: init => child_init  !?
   end type

contains

   subroutine parent_init(self, a)
      class(parent), intent(inout) :: self
      integer, intent(in) :: a
      self%a = a
   end subroutine

   subroutine child_init(self, a, b)
      class(child), intent(inout) :: self
      integer, intent(in) :: a, b
      call self%init(a)
      self%b = b
   end subroutine

end module supe

program main
   use supe, only: parent, child
   implicit none

   type(child) :: kid

   call kid%init(1, 2)
   print *, kid%a, kid%b

end program
  • Is this the proper equivalent to the abovementioned python snippet or am I complicating too much?
  • Is there some equivalent to super().method, other than an explicit/direct call to parent_method ?

Thanks.

1 Like

@HugoMVale ,

It may help if you see the __Init__ method in Python as kinda equivalent to a class constructor in an object-oriented approach. You will note the __Init__ function is invoked every time an object is instantiated in Python for a class.

Note Fortran does not quite have the same “class” constructor scheme though it has default initialization option for derived type components and a somewhat limiting structure construction semantics which would need to be invoked explicitly in a copy assignment instruction. Additionally, Fortran has the option also for a generic function interfaces with the same name as the derived type which can somewhat serve similar purposes but it’s not quite the same as class construction in Python (or C++, etc.).

Your approach of a generic binding is about as good as it can get in Fortran as per the current language standard.

TL;DR: Other than default initialization of derived type components, “explict/direct call” is effectively what is stipulated in Fortran for “class” inialization.

module m
   type :: parent
      integer :: a = 1
   end type
   type, extends(parent) :: child
      integer :: b = 2
   end type
end module
   use m
   type(child) :: kid1, kid2

   print *, kid1%a, kid1%b

   kid2 = child( a=3, b=4 )
   print *, kid2%a, kid2%b

end
4 Likes

Thanks a lot, @FortranFan. I realize that choosing the __init__ method to illustrate the question was not a clever choice, because this is a special method and, thus, renders the question ambiguous. My question was not triggered by (or limited to) the initialization of the derived type. So, I guess I am stuck with generic! :slight_smile:

Interestingly enough, FORD does parse those generic interfaces as “constructors”, see an example here. Nevertheless I agree with you and was a bit frustrated about it, since the interface was not really fully “functional” as a constructor, namely I could not use it to declare a parameter variable: gfortran complains that only intrinsic functions can appear in a parameter definition and/or constructors. I tried removing my “custom constructor” and use the default one and yes, that worked fine in the parameter definition.