Passed-object dummy argument of a procedure pointer component in an extending type

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

The compiler that accepts the shown case is nonconforming.

A procedure pointer component of a derived type does not have the overriding semantics of a type-bound procedure. Thus the procedure target must match the characteristics of the specified interface, including with the declared type of the passed-object dummy argument.

I’ve checked @aradi’s code with gfortran 12.2.0 and ifort 2021.8.0 (on Ubuntu 22.04).
It’s Intel compiler that does not complain:

$ ifort -stand=f18 -c extpoint.f90 
$   # no warnings/errors here, extpoint.o file created
$ gfortran-12 -std=f2018 -c extpoint.f90 
extpoint.f90:32:29:

   32 |     exttype = extending_type(extending_routine)
      |                             1
Error: Interface mismatch for procedure-pointer component ‘routine’ in structure constructor at (1): Type mismatch in argument 'this' (CLASS(base_type)/CLASS(extending_type))

See this, a support request has already been placed with Intel Service Center: