Traditional vs. parameterized derived types

After reading the article Object-Oriented Programming in Fortran 2003
Part 3: Parameterized Derived Types
by Mark Leair I took the code of @ivanpribec that defines a parameterized derived type (PDT) and defined an equivalent traditional derived type to understand the advantages of PDTs, which I may tweet about:

  1. With a PDT one can concisely declare a type with a fixed size.
  2. A PDT can be generic to various KINDs.
  3. The definition of the PDT spells out how the component dimensions relate to each other. For a DT one can write comments about dimensions, as shown, but such comments can be wrong.
  4. For a DT the reader must search for the subroutine that allocates the DT, and that subroutine must be kept consistent with the DT definition if a component is added.
  5. With a DT the user may allocate components directly and get them wrong, or deallocate or some components and not others. And with allocation on assignment, you cannot easily tell from looking at the code where component allocations are occurring, perhaps inadvertently. Thus PDTs are safer.

The disadvantages of PDTs are that they are not as well supported by all compilers and that fewer Fortranners are familiar with them.

module lu_mod
implicit none
integer, parameter :: sp = kind(1.0), dp = kind(1.0d0)
! parameterized derived type from Ivan Pribec 
! https://bit.ly/3sWPCOT
type :: lu_work(wp,n)
    integer, kind :: wp = dp
    integer, len  :: n
    real(wp)      :: a(n,n),b(n)
    integer       :: ipiv(n)
    logical       :: factorized = .false.
end type lu_work
! traditional derived type (dt) -- KIND is hard-coded
type :: lu_work_dt
    real(dp), allocatable :: a(:,:)  ! (n,n)
    real(dp), allocatable :: b(:)    ! (n)
    integer , allocatable :: ipiv(:) ! (n)
    logical               :: factorized = .false.
end type lu_work_dt
contains
pure elemental subroutine alloc(x,n)
type(lu_work_dt), intent(out) :: x 
! components of x deallocated since intent(out)
integer         , intent(in)  :: n
allocate (x%a(n,n),x%b(n),x%ipiv(n))
end subroutine alloc
end module lu_mod

program test_lu
use lu_mod, only: lu_work, lu_work_dt, sp, alloc
implicit none
type(lu_work(n=5))                    :: w ! fixed size
type(lu_work(n=:))      , allocatable :: x
type(lu_work(wp=sp,n=:)), allocatable :: y ! single precision
type(lu_work_dt)                      :: z
integer                               :: n
n = 5
allocate (lu_work(n=n)::x) ! double precision by default
allocate (lu_work(wp=sp,n=n)::y) ! single precision
allocate (z%a(n,n),z%b(n),z%ipiv(n)) ! allocate dt
! better to allocate derived type in subroutine as below
call alloc(z,n)
! check the shapes and kinds of allocated components
print*,shape(x%a),shape(x%b),shape(x%ipiv) ! 5 5 5 5
print*,shape(z%a),shape(z%b),shape(z%ipiv) ! 5 5 5 5
print*,kind(x%a),kind(y%a),kind(z%a) ! 8 4 8
end program test_lu

There are a few posts from @FortranFan, which offer a good summary of the benefits of PDT. I was able to locate one of them:

A second post offered an example of a matrix class, where one could see how PDT’s help you write less code (on the caller side) and instead build directly upon Fortran built-in semantics. This is related to your point #4; instead of a custom procedure for allocation, the caller will directly use the built-in allocate.

Edit: I’m not 100 % sure, but it might have been this one - Julia: Fast as Fortran, Beautiful as Python - #160 by FortranFan