I had guessed as much and that’s why I suggested the alternative above and where I mentioned further subclassing.
Owing to certain other gaps and issues with the language such as with generics and lack of built-in standard intrinsic derived types for utilities (a la STL “classes”), it incentivizes library and solution developers with Fortran to veer toward deeper hierarchies when it comes to OOP and which then require certain flexibility in the language and also an awareness of them to use the facility adequately.
I’m not sure what the standard says about this. (Not that I’m suggesting you use it, though it sort of does what you want, and sort of doesn’t.) The Intel compiler is happy with it and it runs ok unless I enable null pointer checking when it fails with “Attempt to use pointer PARENT when it is not associated with a target” in the call to self%parent%say_hello. Presumably without the check the parent component is automatically allocated before the call.
module parent_m
implicit none
private
type, abstract, public :: parent_t
type(concrete_parent_t), allocatable :: parent
contains
private
procedure, public :: say_hello => say_hello_parent
end type
type, extends(parent_t), public :: concrete_parent_t
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%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
Yes. I should have checked in the debugger. Of course there is no allocation. Parent remains undefined. I suppose the compiler knows where the bound procedure is whether parent is allocated or not and calls it without checking. No doubt things would start to get ugly if other components of parent were referenced. (Initially I had allocated parent in a constructor for child_t but found it didn’t make any difference whether the constructor was used or not so left it out.)