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?