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-name
s 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.objC:\Temp>p.exe
Hello from child_t
Hello from parent_tC:\Temp>