Call overridden procedure of abstract parent type

I’m trying to call a procedure of an abstract derived type, that I’ve extended from, but from within a procedure that overrides that procedure of the parent type. I.e. the following MWE:

module parent_m
    implicit none
    private
    public :: parent_t

    type, abstract :: parent_t
    contains
        private
        procedure, public :: say_hello
    end type
contains
    subroutine say_hello(self)
        class(parent_t), intent(in) :: self

        print *, "Hello from parent_t"
    end subroutine
end module

module child_m
    use parent_m, only: parent_t

    implicit none
    private
    public :: child_t

    type, extends(parent_t) :: child_t
    contains
        private
        procedure, public :: say_hello
    end type
contains
    subroutine say_hello(self)
        class(child_t), intent(in) :: self

        print *, "Hello from child_t"
        call self%parent_t%say_hello
    end subroutine
end module

program main
    use child_m, only: child_t

    implicit none

    type(child_t) :: child

    call child%say_hello
end program

I’ve tried compiling with 3 different compilers (gfortran, nag and intel) and all reject the attempt to call the parent, with the following errors:

call_parent.f90:36:17:

   36 |         call self%parent_t%say_hello
      |                 1
Error: Base object for type-bound procedure call at (1) is of ABSTRACT type 'parent_t'
Error: call_parent.f90, line 36: SELF%PARENT_T is of abstract TYPE(PARENT_T)
call_parent.f90(36): error #8314: If the rightmost part-name is of abstract type, data-ref shall be polymorphic.   [PARENT_T]
        call self%parent_t%say_hello
------------------^
call_parent.f90(36): error #8422: If the component immediately preceding the type-bound procedure is abstract, the entire data reference before the procedure name must be polymorphic.   [PARENT_T]
        call self%parent_t%say_hello
------------------^

And all related questions I’ve found on various forums suggest that this is only legal if the parent type is not abstract.

Could anyone point me to the place in the standard that makes this restriction and explain why this restriction is necessary?

3 Likes

@everythingfunctional ,

From what I recall, the restriction comes into effect by deductive reasoning: for type-bound procedures, sections such as 15.5.6 Resolving type-bound procedure references stipulate the procedure reference to be the one bound to the dynamic type of the data-ref (the part to the left of % token). Since the dynamic type cannot be abstract, it rules out options such as self%parent_t%say_hello.

I can see how reading that section one could come to the conclusion of that constraint, but is it technically necessary? Could an exception be made for this case? Or is there something I’m missing.

It seems pretty clear to me what procedure is intended to be called, but maybe there are edge cases I’m missing.

I should add there is additional deduction based on an inferential process that comes into play with type extension.

Under section 7.5.7.2 Inheritance, paragraph 2, the standard states, “An extended type has a scalar, nonpointer, nonallocatable, parent component with the type and type parameters of the parent type.”

Since the type of a component of a derived type cannot be abstract - it has to be a concrete extension of it - this too rules out ..%parent%.. in any context where parent can be abstract. That is, as a data reference (e.g., ..%parent%x) or as a type-bound procedure one.

Re: “is it technically necessary?”, unless I’m overlooking something, I think the answer is yes.

I think the reasoning for this will be one cannot construct self-standing objects of an abstract type given there can be deferred procedures with said type; and because the semantics of "…%parent%…` reference is set up to resolve to a specific binding, it can lead to a hole that the standard bearers and implementations will want to avoid altogether.

Is there a particular reason you are seeking this? Why not workaround the issue with a slightly different design with the abstract parent type if you are in a position to modify it?

I’m not sure I would consider ...%parent%.. to be a self-standing object though. Of course an abstract type can have deferred procedures, but the specific procedure I’m trying to call isn’t deferred, and the compiler should be able to know that at this point.

Yes, I could use a slightly different design, but it involves making something public that I’d rather not need to and involves otherwise unnecessary code duplication.

This is a pattern that I think would be quite common, and is supported by other languages. Python’s .super comes to mind, but I believe it’s common to call parent constructors in C++ as well. The basic pattern is “my type would like to augment the behavior of this procedure, but the original implementation is still relevant”. In my case I’d like to handle a special case for the extended type, i.e.

if (something_specific_to_child) then
  answer = child_specific_logic
else
  answer = self%parent%original_implementation()
end if

But I could also see something like the following being common.

subroutine init(self)
  class(child), intent(inout) :: self

  call self%parent%init
  ! and now set up some child specific stuff too
end subroutine

Requiring the details of the initial implementation be made public and the logic duplicated seems to me like bad code design solely due to a poor language design decision. I think this is a common pattern in OOP that the committee should at least consider.

Also, once I’m done with the workaround, I’ll come back and point to it. It’s in an open source project.

Note my point is not that ..%parent%.. is a self-standing object. Rather the semantics in the Fortran language standard are such that in order for a parent derived type to be accessible as a component of an extended type, as in say ..%parent%.. form, said component has to be able to be both the declared type and the dynamic type in order for procedure bindings to get resolved and so forth. That is, such a component cannot be abstract.

I’m not sure I understand the issue here re: “implementation be made public”. The code in the original post shows the abstract derived type thingy say_hello to be public.

OO facilities in Fortran can do with some improvement but I am not convinced there is a language design issue in this particular case. Instead the way OO is designed in Fortran, albeit with some forced verbosity and explicitness e.g., with binding-name and specific binding, offers both the advantage and a degree of flexibility for scientists and engineers to comprehend OO approach and use it better for technical computing. To me, that seems to extend to the situations shown in the quoted comment also, such as with %init case.

In the example say_hello is public, but what it does/how it does it is not. In more complex examples there may be local parameters, private module procedures that one does not necessarily desire to make public, and complex internal logic that one would prefer not to duplicate.

When I wrote above “OO facilities in Fortran can do with some improvement”, among other things I did have in mind some of the knotty situations that arise due to the MODULE-level accessibility restrictions in the language standard with PUBLIC/PRIVATE and how that can impact OO “class” design of one’s codes. However within the specific context of this thread and the original post and the code shown therein, such aspects appear extraneous. So different MWEs with suitable detail, perhaps in a different thread, will help with that discourse.

For the specific issue with the error at instruction call_parent.f90:36:17 and whatever business need can be driving it, it seems to me working around it by employing existing language facilities might be a better option.

I often have this problem. My workaround it to add the suffix “_abstract” to the suboutine of parent, e.g.:

subroutine init(self)
  class(child), intent(inout) :: self

  call self%init_abstract
  ! and now set up some child specific stuff too
end subroutine

And generally init_abstract might stay private.

1 Like

@everythingfunctional ,

Did you settle on a workaround that you can share here? I mean, as you can illustrate readily with simple MWEs like the code in the original post and with the init case you added?

I did. It was for my erloff project, for the is_type TBP of the message_t type (and types extended from it). I made the procedure itself public, so that overriding procedures could call it explicitly. That pattern repeats itself for the error_t type, which is extended from message_t and has types extend from it. This was to me the least undesirable solution, if not ideal.

To demonstrate the solution based on my prior MWE.

module parent_m
    implicit none
    private
    public :: parent_t, say_hello_default

    type, abstract :: parent_t
    contains
        private
        procedure, public :: say_hello => say_hello_default
    end type
contains
    subroutine say_hello_default(self)
        class(parent_t), intent(in) :: self

        print *, "Hello from parent_t"
    end subroutine
end module

module child_m
    use parent_m, only: parent_t, say_hello_default

    implicit none
    private
    public :: child_t

    type, extends(parent_t) :: child_t
    contains
        private
        procedure, public :: say_hello => say_hello_child
    end type
contains
    subroutine say_hello_child(self)
        class(child_t), intent(in) :: self

        print *, "Hello from child_t"
        call say_hello_default(self)
    end subroutine
end module

program main
    use child_m, only: child_t

    implicit none

    type(child_t) :: child

    call child%say_hello
end program
1 Like

An alternative workaround is as follows:

   ..
   type, abstract, public :: parent_t
   contains
      private
      procedure, public :: say_hello_default
      procedure, public :: say_hello => say_hello_default
   end type
   ..

This can help make it easier to work with extended types in certain situations e.g., further subclassing of child_t in a different module (and which may be in another program package altogether) with possibly no access to module hosting the parent abstract “class”. Note this workaround is based on the flexibility in the Fortran language standard where 2 or more binding-names of type-bound procedures of a derived type can point to the same specific procedure-name. Extended types then override the binding-name corresponding to a “generic name” (say_hello, init, etc.), leaving the default name as-is.

Here`s how it can look with the MWE in the original post:

module parent_m
   implicit none
   private

   type, abstract, public :: parent_t
   contains
      private
      procedure, public :: say_hello_default
      procedure, public :: say_hello => say_hello_default
   end type
contains
   subroutine say_hello_default(self)
      class(parent_t), intent(in) :: self

      print *, "Hello from parent_t"
   end subroutine
end module

module child_m
   use parent_m, only: parent_t

   implicit none
   private

   type, extends(parent_t), public :: child_t
   contains
      private
      procedure, public :: say_hello => say_hello_child !<-- override the "generic"
   end type
contains
   subroutine say_hello_child(self)
      class(child_t), intent(in) :: self

      print *, "Hello from child_t"
      call self%say_hello_default()  !<-- invoke the base method as needed
   end subroutine
end module

program main
   use child_m, only: child_t

   implicit none

   type(child_t) :: child

   call child%say_hello()
end program

C:\Temp>ifort /standard-semantics /warn:all /stand:f18 p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.1.2 Build 20201208_000000
Copyright (C) 1985-2020 Intel Corporation. All rights reserved.

p.f90(12): remark #7712: This variable has not been used. [SELF]
subroutine say_hello_default(self)
--------------------------------^
Microsoft (R) Incremental Linker Version 14.26.28806.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\Temp>p.exe
Hello from child_t
Hello from parent_t

C:\Temp>

Not coming from an OOP background or experienced in using Fortran OOP features I’m probably missing something but, for what it’s worth, I would have done something like:

module grand_parent_m
   implicit none
   private
   
   type, abstract, public :: grand_parent_t
   contains
      private
      procedure(say_hello_ai), public, deferred :: say_hello
   end type
   
   abstract interface
       subroutine say_hello_ai(self)
       import grand_parent_t
       class(grand_parent_t), intent(in) :: self
       end subroutine say_hello_ai
   end interface
end module

module parent_m
   use grand_parent_m, only:grand_parent_t
   implicit none
   private

   type, extends(grand_parent_t), public :: parent_t
   contains
      private
      procedure, public :: say_hello => say_hello_parent
   end type
contains
   subroutine say_hello_parent(self)
      class(parent_t), intent(in) :: self

      print *, "Hello from parent_t"
   end subroutine
end module

module child_m
   use parent_m, only: parent_t

   implicit none
   private

   type, extends(parent_t), public :: child_t
   contains
      private
      procedure, public :: say_hello => say_hello_child !<-- override the "generic"
   end type
contains
   subroutine say_hello_child(self)
      class(child_t), intent(in) :: self

      print *, "Hello from child_t"
      call self%parent_t%say_hello()
   end subroutine
end module

program main
   use child_m, only: child_t

   implicit none

   type(child_t) :: child

   call child%say_hello()
end program

It compiles and runs ok with Intel® Visual Fortran Compiler 19.1.2.254

This may be slightly better. I may use this instead. Thanks.

I had seen this suggested, and even considered it, but in my case it doesn’t work. grandparent has a default implementation, parent has another implementation that overrides grandparent, but also needs to call the default. parent must also be abstract because of other deferred bindings. And then child has an implementation that overrides parent, but also needs to call it. I.e.

module grand_parent_m
   implicit none
   private
   
   type, abstract, public :: grand_parent_t
   contains
      private
      procedure, public :: say_hello_grandparent
      procedure, public :: say_hello => say_hello_grandparent
   end type
contains
  subroutine say_hello_grandparent(self)
    class(grand_parent_t), intent(in) :: self

    print *, "Hello from grand_parent_t"
  end subroutine
end module

module parent_m
   use grand_parent_m, only:grand_parent_t
   implicit none
   private

   type, extends(grand_parent_t), abstract, public :: parent_t
   contains
      private
      procedure, public :: say_hello_parent
      procedure, public :: say_hello => say_hello_parent
   end type
contains
   subroutine say_hello_parent(self)
      class(parent_t), intent(in) :: self

      print *, "Hello from parent_t"
      call self%say_hello_grandparent
   end subroutine
end module

module child_m
   use parent_m, only: parent_t

   implicit none
   private

   type, extends(parent_t), public :: child_t
   contains
      private
      procedure, public :: say_hello => say_hello_child !<-- override the "generic"
   end type
contains
   subroutine say_hello_child(self)
      class(child_t), intent(in) :: self

      print *, "Hello from child_t"
      call self%say_hello_parent()
   end subroutine
end module

program main
   use child_m, only: child_t

   implicit none

   type(child_t) :: child

   call child%say_hello()
end program

Fair enough, though I imagined that grand_parent_t would declare all the deferred bindings. parent_t would have to override them all, with procedures that do nothing if neccessary. Any type that extends parent_t can override whatever it needs to. grand_parent_t doesn’t need to be referenced outside its module and the ‘extends’ of parent_t so parent_t can have the default implementation as in your original post. (Grand parent has passed on his DNA but is in the ground so is unable to say hello)

Is what I am missing is that you need to have the compiler report procedures not overridden in types extended from parent_t? As I said I’m not familiar with using OOP features in fortran and haven’t used abstract types before. I was interested in the post and put together some code that more-or-less did what was in the original post. I’ve realised that the less is the abstract part of parent_t.

Exactly. An abstract type gives you two (complimentary) things.

  1. You can define a consistent interface that all types extended from it are guaranteed to support
  2. The compiler will tell you if you forgot anything

By putting a type in the middle that isn’t abstract, but the procedures don’t actually do anything, you lose number 2. Not always a deal breaker in all cases, but not desirable if you can avoid it.