Intel Fortran Compiler Bug: overloading binary and unary operator(-) and use with extended types

Sebastian, could you please explain why you seem to want to have the factor optional ?
That’s why in my first answer I said “what you actually want to achieve”.
In any case, you could not call your custom init_vec vector constructor for initialising parameter entities.
But, I might miss something.

It could actually be a compiler bug as mentioned in the comments of the link you report here. I slightly modified your implementation, which generated an ICE.
This, which I think should reproduce what you want to achieve, compiles and runs correctly:

module mod
   implicit none
   type :: base1
      integer :: i
   contains
      generic :: proc => baseProc1_
      procedure, pass(this) :: baseProc1_
   end type
   type, extends(base1) :: ext1
   end type

   type :: base2
      integer :: i
   contains
      generic :: proc => baseProc2_, anotherProc_
      procedure, pass(this) :: baseProc2_, anotherProc_
   end type
   type, extends(base2) :: ext2
   end type
contains

   function baseProc1_(this)
      class(base1), intent(in) :: this
      type(base1) :: baseProc1_
      print *, ' This is base proc 1 ! '
      baseProc1_ = base1(this%i + 1)
   end function

   function baseProc2_(this)
      class(base2), intent(in) :: this
      type(base2) :: baseProc2_
      print *, ' This is base proc 2 ! '
      baseProc2_ = base2(-this%i)
   end function

   function anotherProc_(this, i)
      class(base2), intent(in) :: this
      type(base2) :: anotherProc_
      integer, intent(in) :: i
      print *, ' This is another proc for base 2 ! '
      anotherProc_ = base2(this%i + i)
   end function
end module


program prog
   use mod
   implicit none
   type(ext1), parameter :: e1 = ext1(1)
   type(ext2), parameter :: e2 = ext2(5)

   print *, e1%proc()
   print *, e2%proc()
   print *, e2%proc(5)
end program

As for your example, this is another proposition that works. But still, by also reading the other thread, it might not suit what you actually need.

module mo_vec

   type, public :: vector
      real :: x, y
   end type vector

   interface operator(-)
      module procedure negVec_
      module procedure diffVec_
      module procedure negVecP_
      module procedure diffVecP_
   end interface

   ! interface assignment(=)
   !    module procedure assignVec_
   !    module procedure assignVecP_
   ! end interface

   interface vector
      procedure init_vec
   end interface vector

   type, public, extends(vector) :: vector_parameter
   end type

contains

   ! Your custom defined vector constructor
   elemental pure type(vector) function init_vec(x, y, factor)
      real, intent(in) :: x, y, factor
      
      init_vec = vector(x * factor, y * factor)
   end function init_vec

   pure function diffVec_(this, that)
      type(vector), intent(in)  :: this, that
      type(vector) :: diffVec_

      diffVec_ = vector(this%x-that%x, this%y-that%y)
   end function diffVec_

   pure function diffVecP_(this, that)
      type(vector_parameter), intent(in)  :: this, that
      type(vector_parameter) :: diffVecP_

      diffVecP_ = vector_parameter(this%x-that%x, this%y-that%y)
   end function diffVecP_

   pure function negVec_(this)
      type(vector), intent(in)  :: this
      type(vector) :: negVec_
      
      negVec_ = vector(-this%x, -this%y)
   end function negVec_

   pure function negVecP_(this)
      type(vector_parameter), intent(in)  :: this
      type(vector_parameter) :: negVecP_
      
      negVecP_ = vector_parameter(-this%x, -this%y)
   end function negVecP_

end module mo_vec
 

program vec_test
   use mo_vec
   implicit none
   type(vector_parameter), parameter :: vec_x = vector_parameter(1., 0.)
   type(vector_parameter), parameter :: vec_y = vector_parameter(0., 1.)

   print *, vec_x - vec_y
   print *, vec_x - -vec_y
   print *, vector(1., 2., 5.)
end program vec_test