I have an interesting case affecting the behavior of procedure pointers when a type is extended, where different compiler seem to have different opinions about what is allowed by the standard and what is forbidden.
GIVEN a procedure pointer component in a base type (base_type
), which has the PASS
attribute (implicitly or explicitly), and an extending type (extending_type
) of this base type,
WHEN I initialize extending_type
via its structure constructor
THEN am I allowed to associate the procedure pointer component with a routine, where the first (passed-object) dummy argument is of the polymorphic type class(extending_type)
?
It seems to me, that 7.5.4.5 / C761 in the Fortran 2018 draft is relevant here, but I have difficulties to understand, whether this allows (or even requires) the association in an extending type with a procedure having a passed-object dummy argument of type class(extending_type)
, or whether it means, that the target procedure must have class(base_type)
as its passed-object dummy argument even in extending types.
Does anybody has any thoughts on this?
module testmod
implicit none
type :: base_type
procedure(routine_i), pointer :: routine
end type base_type
abstract interface
subroutine routine_i(this)
import :: base_type
class(base_type), intent(inout) :: this
end subroutine routine_i
end interface
type, extends(base_type) :: extending_type
end type extending_type
contains
subroutine extending_routine(this)
class(extending_type), intent(inout) :: this
end subroutine extending_routine
function exttype()
type(extending_type) :: exttype
! I am not sure, whether this is correct according 7.5.4.5 / C761 in the Fortran 2018 draft.
! One compiler accepts it, on other one complains, that in the constructor for type
! EXTENDING_TYPE, the procedure pointer component ROUTINE argument THIS
! is of type BASE_TYPE, but argument THIS in value EXTENDING_ROUTINE is of type
! EXTENDING_TYPE
exttype = extending_type(extending_routine)
end function exttype
end module testmod