Parameterized derived types and type extensions

Dear all,

I am trying to extend an abstract type with a (kind) parameterized derived type (PDT) in Fortran. My problem is that I can’t figure out how to override deferred, type bound procedures in this special setting. Below is a short, completely made up example that hopefully illustrates the issue:

module vector_m
  implicit none
  integer, parameter :: sp = selected_real_kind(6, 37)   
  integer, parameter :: dp = selected_real_kind(15, 307) 

  type, abstract :: vector_t
   contains
     procedure(first_component_as_strg_i), deferred :: first_component_as_strg
  end type vector_t

  abstract interface
     function first_component_as_strg_i(this) result(c)
       import :: vector_t
       implicit none
       class(vector_t)                :: this
       character(len=:),  allocatable :: c
     end function first_component_as_strg_i
  end interface
  
  type, extends(vector_t) :: real_vector_t(kr)
     integer, kind :: kr
     real(kr), allocatable :: comp(:)
   contains
     ! QUESTION: How do I override first_component_as_strg?
     !
     ! This works with ifx in this particular example (only the 1st procedure in
     ! the comma separated list seems to be considered)
     procedure :: first_component_as_strg => &
                         first_component_as_strg_sp,first_component_as_strg_dp
     ! This doesn't work with ifx:
     ! procedure :: first_component_as_strg => &
     !                    first_component_as_strg_dp,first_component_as_strg_sp
     !
     ! My feeling is that I need some sort of generic construct here, but can't
     ! figure out the right syntax.
  end type real_vector_t

contains
  
  function first_component_as_strg_sp(this) result(c)
    implicit none
    class(real_vector_t(sp))      :: this
    character(len=:), allocatable :: c
    character(len=24) :: chelp
    write(chelp,*) this % comp(1)
    c = trim(chelp)
  end function first_component_as_strg_sp
 

  function first_component_as_strg_dp(this) result(c)
    implicit none
    class(real_vector_t(dp))      :: this
    character(len=:), allocatable :: c
    character(len=24) :: chelp
    write(chelp,*) this % comp(1)
    c = trim(chelp)
  end function first_component_as_strg_dp
  
end module vector_m

program testprog
  use vector_m
  implicit none
  type(real_vector_t(sp)) :: rvec
  character(len=:), allocatable :: strg
  rvec % comp = [1._sp,2._sp]
  strg = rvec % first_component_as_strg ()
  print*, strg
end program testprog

In this (rather silly) example, the goal is to have an abstract type “vector_t”, that might not only be extended by a non-parameterized type, but also by a PDT - in this example by the type “real_vector_t”. The abstract type “vector_t” defines a deferred function “first_component_as_strg” which returns the first component of a vector as a string, which should be possible for arbitrary vectors.

My Problem now is: How do I override the function “first_component_as_strg” in the definition of real_vector_t?

I know how to do this for the case where vector_t is parameterized (using a generic statement in its type definition), but in this special case, I just don’t get it. I don’t feel that this example is too exotic either - similar situations readily arise if one fully embraces the PDT concept in complex codes.

Finally, I know that PDTs are still not widely used because of generally poor compiler support, but the Intel compiler seems to be doing quite well by now.

Any help is highly appreciated!

Here is a slightly modified version of your example (with some “noise” removed) that I think does what you are trying to accomplish:

module vector_m

   implicit none

   integer, parameter :: sp = selected_real_kind(6, 37)   
   integer, parameter :: dp = selected_real_kind(15, 307) 

   type, abstract :: vector_t
   contains
      procedure(first_as_strg), deferred :: first_as_strg_sp
      procedure(first_as_strg), deferred :: first_as_strg_dp
   end type vector_t

   abstract interface
      function first_as_strg(this) result(c)
         import :: vector_t
         implicit none
         class(vector_t)            :: this
         character(:),  allocatable :: c
      end function first_as_strg
   end interface

   type, extends(vector_t) :: real_vector_t(kr)
      integer, kind :: kr
      real(kr), allocatable :: comp(:)
   contains
      generic :: first_component_as_strg => first_as_strg_sp, first_as_strg_dp
      procedure :: first_as_strg_sp
      procedure :: first_as_strg_dp
   end type real_vector_t

contains

   function first_as_strg_sp(this) result(c)
      class(real_vector_t(sp))  :: this
      character(:), allocatable :: c
      character(24) :: chelp
      write(chelp,'(1p,e14.7)') this%comp(1)
      c = trim(chelp)
   end function first_as_strg_sp
   
   function first_as_strg_dp(this) result(c)
      class(real_vector_t(dp))  :: this
      character(:), allocatable :: c
      character(24) :: chelp
      write(chelp,'(1p,e23.16)') this%comp(1)
      c = trim(chelp)
   end function first_as_strg_dp

end module vector_m


program testprog

   use vector_m

   implicit none

   type(real_vector_t(sp)) :: rvec_sp
   type(real_vector_t(dp)) :: rvec_dp

   rvec_sp%comp = [1._sp,2._sp]
   rvec_dp%comp = [1._dp,2._dp]

   print*, rvec_sp%first_component_as_strg()
   print*, rvec_dp%first_component_as_strg()

end program testprog

This code, which I quickly tested with both ifx and flang-20, gives the result:

  1.0000000E+00
  1.0000000000000000E+00

which I believe is what you were trying to achieve.

The important changes, as compared to your original example, are that I provided deferred bindings for both versions of the first_as_strg functions in the abstract derived type, and that I used a generic binding for those in the implementing type.

Hi kkifonidis,

thank you for the quick reply! Unfortunately, this is not exactly what I had in mind. Maybe the example code I posted was too condensed or I did not explain things properly. What I am looking for is a solution which guarantees the following:

  • Every object x that is class(vector_t) - and not just an object that is type(real_vector_t) - has access to a type bound function x%first_component_as_strg().
  • The types that extend the base type vector_t might be PDTs and non-PDTs. For example, I might have the PDT real_vector_t and a non-parameterized type int_vector_t that both extend vector_t.
  • The implementation should be easily extendable in the future. Perhaps at some point, I would like to add cmplx_vector_t, char_vector_t, …. or some vector of derived types.
  • But already now I would like to be able to implement code that can rely on the fact that I can get the first component as a string. In particular, this code cannot rely on select type() constructs, because I don’t know yet which types will exist in the future.

I acknowledge that the above example might seem a bit silly and made up, which it surely is. In fact I am working on a large and complex project where the same abstract issue appears in a different context. But I believe that the desire to extend an abstract base type with both PDTs and non-PDTs should be quite common. And as soon as the base type has a deferred TBP, I can’t figure out how to do it.

1 Like

In case anyone is interested, there’s also solid support for kind type parameters in LLVM flang and in recent builds of the Numerical Algorithm Group compiler. And this is a great time to submit PDT bug reports on gfortran. Gfortran developer Paul Thomas is in the midst of addressing many PDT-related issues so stay tuned for better PDT support to come in gfortran 16.

5 Likes

Very briefly, I think your full requirements cannot be met with what the present language has to offer. I’ll try to elaborate in a later post.

No, not at all. The full design that you are trying to implement is a perfectly legitimate use case.

In fact, it is one of the use cases that our Traits proposal was designed to make possible, and that I think cannot be (reasonably) coded using both the present language, and the committee’s proposed generics design (because it requires interoperability between true generic, and object-oriented programming, which both the present language and the committee’s generics lack).

I’ll provide an example (in a later post) of how it could be coded using the Fortran extensions that we propose in our document.

@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.

Thanks a lot for this detailed answer. This actually saves me a lot of time. I naively assumed that this case is quite common and therefore should have been considered since F2003 introduced both PDTs and type extension.
I spent a few hours studying your Traits proposal and even though I haven’t made it all the way through yet, I really enjoyed the reading process. Being a Fortran practitioner developing CFD codes for many years, this addresses exactly what I have been missing most from the language. I clearly lack the expertise to judge wether or not this is the best way to go for Fortran, but to me the presented code examples (and the one you posted above) look very elegant and intuitive and yet the approach seems very powerful and general.

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.

If at some point (no rush) you or someone else could provide a brief explanation or point me to an adequate resource, that would indeed be great. It wasn’t obvious to me when looking into the Fortran standard documents. And there seems to be no other resource on the web that addresses exactly this issue - at least I did not find anything. So it might be of interest to others as well?

2 Likes

Parameterized derived types have two “kinds” of parameters: KIND and LEN. While the LEN parameters can have any (positive) value, the KIND parameters must be known at compile time.

So, for your code to work, a KIND must be chosen. Here’s a simplified version of your code that illustrates the limitation:

module vector_m
    use ISO_FORTRAN_ENV

    implicit none
    private

    type, abstract, public :: vector_t
    contains
        procedure(i_first_component_as_strg), deferred :: first_component_as_strg
    end type vector_t

    abstract interface
        function i_first_component_as_strg(this) result(c)
            import :: vector_t
            character(len=:), allocatable :: c
            class(vector_t), intent(in) :: this
        end function
    end interface

    type, extends(vector_t), public :: real_vector_t(kr, l)
        integer, kind :: kr
        integer, len :: l
        real(kr) :: comp(l)
    contains
        ! In Fortran, all type-bound procedures are overridable by default.
        ! In this case, the procedure must be overridden because this derived
        ! type is not abstract.
        ! Since KIND parameters must be known at compile time, you must choose
        ! which procedure does the overriding.
        procedure :: first_component_as_strg => first_component_as_strg_real32

        ! But there's no issue in providing your own generic for the parameterized
        ! derived type.
        generic :: to_string_first => first_component_as_strg_real32, first_component_as_strg_real64
        procedure :: first_component_as_strg_real32, first_component_as_strg_real64
    end type

contains
    function first_component_as_strg_real32(this) result(c)
        character(len=:), allocatable :: c
        class(real_vector_t(REAL32, *)), intent(in) :: this
        c = repeat(' ', 24)
        write(c,'(g0)') this%comp(1)
        c = trim(c)
    end function

    function first_component_as_strg_real64(this) result(c)
        character(len=:), allocatable :: c
        class(real_vector_t(REAL64, *)), intent(in) :: this
        c = repeat(' ', 24)
        write(c,'(g0)') this%comp(1)
        c = trim(c)
    end function
end module vector_m

program testprog
    use ISO_FORTRAN_ENV
    use vector_m

    implicit none

    type(real_vector_t(REAL32, 2)) :: spvec
    type(real_vector_t(REAL64, 2)) :: dpvec
    character(len=:), allocatable :: strg

    spvec%comp = [1._real32, 2._real32]

    ! the first_component_as_strg() TBP can only be invoked for kr=REAL32
    print*, 'spvec%first_component_as_strg()=',spvec%first_component_as_strg()

    ! but the to_string_first() TBP can be used in both cases

    print*, 'spvec%to_string_first()=', spvec%to_string_first()

    dpvec%comp = [3._real64, 4._real64]
    print*, 'dpvec%to_string_first()=', dpvec%to_string_first()
end program testprog

With ifort (which, btw, was EOL’d by Intel), I get:

$ ifort -diag-disable=10448 pdt-discourse.f90 && ./a.out 
 spvec%first_component_as_strg()=1.000000
 spvec%to_string_first()=1.000000
 dpvec%to_string_first()=   3.00000000000000
1 Like

Dear jwmwalrus,

thanks a lot for your answer! Unfortunately, I do not get your point. Maybe you can explain a little more?

First, I don’t see what LEN parameters have to do with it. My feeling is that in this case, the problem is completely caused by the KIND parameter of the type.

Secondly, I am not surprised that the code you posted does what it does. Indeed, I use similar generic constructs in PDTs all the time. That is kind of my point, actually. My naive understanding is that a PDT object must get its KIND at compile time, which I thought it does in my example. The object rvec is declared to be of type real_vector_t(sp), with sp being a compile time constant. The compiler thus should be able to determine at compile time which procedure (i.e. first_component_as_strg_sp or first_component_as_strg_dp) needs to be called for rvec. And indeed it does so if you use the generic construct inside the definition of real_vector_t itself, as in your example. So the compiler should also be able to determine which procedure to use to override first_component_as_strg for the object rvec at compile time - at least if an appropriate syntax existed to tell the compiler that this is what I want.

So at which point is there any ambiguity at compile time? In fact, I cannot see how such ambiguity could arise for any object of type real_vector_t, because, as you pointed out, the standard requires its KIND parameter to be a compile time constant.

1 Like

There are no restrictions on the values that parameters can take. Here is an example of using negative values, both at compile time and at run time.

program pdtx
   implicit none
   type mytype(lb,ub)
      integer, len :: lb=1, ub=3
      integer :: array(lb:ub)
   end type mytype
   type(mytype) :: default
   type(mytype(-1,1)) :: ctime
   integer :: lb, ub
   write(*,*) 'default:', lbound(default%array), ubound(default%array)
   write(*,*) 'ctime:', lbound(ctime%array), ubound(ctime%array)
   write(*,*) 'input lb, ub:'
   read(*,*) lb, ub
   block
     type(mytype(lb,ub)) rtime
      write(*,*) 'rtime:', lbound(rtime%array), ubound(rtime%array)
   end block
end program pdtx

$ gfortran pdt.f90 && a.out
 default:           1           3
 ctime:          -1           1
 input lb, ub:
-9 -1
 rtime:          -9          -1

I think the only actual contraints are, as aleady mentioned, the KIND type parameters must be known at compile time and the LEN type parameters are allowed to be evaluated at run time. I did the i/o in that example just to ensure that the compiler could not evaluate any expressions at compile time.

[edit] I have since tried the above code successfully with gfortran and nagfor on MacOS. The flang compiler gives:

$ flang --version
Homebrew flang version 21.1.0
Target: arm64-apple-darwin24.6.0
Thread model: posix
InstalledDir: /opt/homebrew/Cellar/flang/21.1.0/libexec
Configuration file: /opt/homebrew/Cellar/flang/21.1.0/libexec/flang.cfg
Configuration file: /opt/homebrew/etc/clang/arm64-apple-darwin24.cfg
$ flang pdt.f90
error: loc("/Volumes/u/shepard/misc/work/pdt.f90":3:9): /private/tmp/flang-20250826-772-f66swm/llvm-project-21.1.0.src/flang/lib/Lower/ConvertType.cpp:487: not yet implemented: parameterized derived types
LLVM ERROR: aborting
1 Like

With LEN parameters you won’t have this issue. Only KIND is restricted to compile-time values.

Since you must pick a KIND value for compile-time purposes, you’re effectively creating multiple derived-types in the same block of code —e.g., you cannot invoke the real32-TBP from the real64-TBP and vice versa.

And again, LEN parameters don’t have that problem, and that’s when PDTs are supposed to shine.

The implemented subroutines get their compile-time values just fine, but you must understand that they correspond to different derived types within the same block of code, so you must pick only one procedure to do the required overriding.

You mentioned that ifx seems to pick only the first one, but that’s just how the type-bound-procedure-stmt is defined by the standard, e.g.:

PROCEDURE [, binding-attr [, binding-attr ...]] :: binding-name [ => procedure-name], binding-name [ => procedure-name] ...

So, for the second procedure in your list, the procedure-name coincides with the binding-name.

@jwmwalrus , thanks again! I realize that I should not have left the line

procedure :: first_component_as_strg => &
                         first_component_as_strg_sp,first_component_as_strg_dp

in my example code, as it makes my question sound like “why doesn’t this work”? In fact, I merely put the line in to broadly illustrate what functionality I was looking for, and when running this, I was confused that changing the order of the functions affects the result. My bad, sorry for the confusion. I should have checked the standard to see that this is indeed conforming, as you rightfully point out.

In fact, my main question was not why this line of code isn’t doing what I want. My question was what syntax I need to use to have the compiler use the correct procedure (i.e. first_component_as_strg_sp or first_component_as_strg_dp) to override first_component_as_strg. I just felt that this should be possible as everything seems to be known at compile time. But there appears to be no syntax that does this. And my feeling is that there must be a deeper reason for this - not just that it was forgotten when F2003 was designed. That is what I still don’t get.

Maybe someone from the Fortran 2003 Standard Committee still hangs around here?

As I see it, the issue is that the abstract derived type represents a single type, whereas the parameterized derived type (with KIND) represents multiple/different types —so maybe that’s a corner case that, given the slow implementations of the feature, nobody in the standard committee has bothered to clarify.

Quality of implementation is another issue —e.g., at one point, ifort/ifx showed the parameters as part of a namelist (haven’t checked the latest ifx, so maybe it’s fixed now.)

This is a very interesting use case, and I can totally see why you would want to do it this way, but current Fortran just doesn’t support it like you’d think. The problem goes all the way back to the fact that kind type parameters and type-bound procedures just play weirdly together. Type extension makes it even more awkward, to the point that it doesn’t really work.

A type-bound procedure represents a single specific procedure, but a specific procedure can only be defined for a single (combination) of specific kind type parameters. So things are already awkward even without type extension, i.e.

type :: my_t(k)
  integer, kind : k
  real(k) :: comp
contains
  procedure :: print_sp
  procedure :: print_dp
end type
contains
subroutine print_sp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine
subroutine print_dp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine

No matter what kind type parameter you specify when declaring a my_t variable, both those subroutines are bound to the type, but only one (or maybe none) of them are actually callable. People generally try and work around this with generic names, like

type :: my_t(k)
  integer, kind : k
  real(k) :: comp
contains
  procedure :: print_sp
  procedure :: print_dp
  generic :: print => print_sp, print_dp
end type
contains
subroutine print_sp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine
subroutine print_dp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine

and now you can just use call my_var%print() for my_t variables declared with either single or double precision.

So, you can’t have multiple overrides for a single procedure, but you can’t make kind type parameters work without it.

I think this is a question the committee should address though. You might be tempted to try something like the following for your example, but I don’t think it’s valid.

type, abstract :: my_abs_t
contains
  procedure(print_i) :: print_k1
  procedure(print_i) :: print_k2
  generic :: print => print_k1, print_k2
end type
abstract interface
  subroutine print_i(self)
    class(my_abs_t) :: self
  end subroutine
end interface

type, extends(my_abs_t) :: my_t(k)
  integer, kind :: k
  real(k) :: comp
contains
  procedure :: print_k1 => print_sp
  procedure :: print_k2 => print_dp
end type
contains
subroutine print_sp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine
subroutine print_dp(self)
  class(my_t(4)) :: self
  print *, self%comp
end subroutine

It also means you have to somehow come up with a distinguishable (in the generic interface sense) second procedure even for types that don’t need a second kind type parameter, but it still has to match the original interface, which I don’t think is possible.

This is a design that I don’t think the committee has considered, but I think we should.

For what it’s worth, I think this is solved by the current templates, it just avoids the kind type parameter by making it a deferred argument.

type, abstract :: my_abs_t
contains
  procedure(print_i) :: print
end type
abstract interface
  subroutine print_i(self)
    class(my_abs_t) :: self
  end subroutine
end interface

template my_t_impl(k)
  deferred integer, parameter :: k
  type, extends(my_abs_t) :: my_t
    real(k) :: comp
  contains
    procedure :: print => print_impl
  end type
contains
  subroutine print_impl(self)
    class(my_t) :: self
    print *, self%comp
  end subroutine
end template
1 Like

@everythingfunctional’s comment has thankfully spared me the writing of another long post, as he has essentially confirmed that true interoperability between “parameterized derived types” (PDTs) and type extension was never considered by the Fortran committees, let alone realized.

I will thus only add that the same committee process, that is responsible for this failure, is still in place to this day, and continues to produce unsound features, like the mentioned “templates”, which equally lack true interoperability with the language’s object-oriented programming items (as it is on record on this forum).

Hence, my advice to (unsuspecting) Fortran programmers who, like the OP, need to write long-lasting codes, is to stay clear of both PDTs, and the said templates.

If you need viable generic programming capabilities in Fortran, consider helping out the LFortran compiler team to provide (sooner) support for the traits-based generics and modern-day OOP features that I’ve mentioned above. Or demand compiler support for these language extensions from the vendors of your hardware.

1 Like

It would be phenomenal if gfortran also supported the PDT kind type parameter properly. The lentype-parameter support is the source of all implementation complexities and is far less critical and useful than kind in my opinion. I think I speak for everyone if I say I am incredibly grateful for Paul’s efforts to fix the Gfortran PDT issues.

1 Like