Parameterized derived types and type extensions

@Stephan_S Here’s how all of the cases of your general design would be implemented with the new Fortran extensions that we propose:

module vector_m

   implicit none

   abstract interface :: IAnyType
   end interface

   abstract interface :: IVector
      function first_component_as_strg() result(c)
         character(:), allocatable :: c
      end function
   end interface
   
   type, sealed, implements(IVector) :: Vector{IAnyType :: T}
      private
      type(T), allocatable :: comp(:)
   contains
      initial :: init
      procedure, pass :: first_component_as_strg => first_as_strg
   end type

contains

   function init(comp) result(res)
      type(T), intent(in) :: comp(:)
      type(Vector{T})     :: res
      res%comp = comp
   end function

   function first_as_strg(self) result(c)
      type(Vector{T}), intent(in)  :: self
      character(:),    allocatable :: c
      character(24) :: chelp
      write(chelp,*) self%comp(1)
      c = trim(chelp)
   end function

end module vector_m


program testprog

   use vector_m

   implicit none

   call client( Vector([1.,2.]) )
   call client( Vector([1.d0,2.d0]) )
   call client( Vector(['John','Anne']) )

contains

   subroutine client(vec)
      class(IVector), intent(in) :: vec
      print*, vec%first_component_as_strg()      
   end subroutine
   
end program testprog

With this approach, there would be no need for the programmer to write multiple types that all implement the IVector interface individually, to cover all your different use cases (although this is, of course, perfectly possible). One could simply use the above Vector generically parameterized type for all of this.

This example is truly just a variation of the Vector example that we already discussed in our proposal.

If anyone would like me to comment on why even the correspondingly simpler use case, that involves only the single and double precision real types, cannot be coded analogously with type extension, and the present language’s PDTs (“parameterized derived types”), then let me know.

EDITS: To the main program, to better illustrate the main capability that @Stephan_S is seeking.