Purpose of kind parameters in derived types

Currently kind parameters are mandated to be compile time constants. Suppose I want to write a library without committing to a value of precision (this is how good libraries should be, user should be able to control the precision used in types and functions) while compiling it. In C++, I will switch from float to double et cetra in the template parameter. In Fortran, this could be even more elegant by leaving the choice of precision to the user via a kind parameter. However, it does allow writing functions/subroutines with arguments of unspecified precision. I feel this is a very severe limitation of a potentially powerful feature which could significantly reduce the use of preprocessors.

1 Like

Are your comments aimed at functions/subroutines, derived types, or both?

For derived types you have the parameterized version, which give you the generic kind. I’ve got an example of a PDT for LU factorization of a square matrix available here.

The derived type comes together quite easily:

  type :: lu_workspace(wp,n)
    integer, kind :: wp
    integer, len :: n
    real(wp) :: a(n,n)
    real(wp) :: b(n)
    integer :: ipiv(n)
    logical :: factorized = .false.
  end type

Problems show up when you start adding procedures. In that case you cannot avoid boilerplate (without resorting to preprocessing):

  integer, parameter :: sp = kind(1.0e0)
  integer, parameter :: dp = kind(1.0d0)

  interface factorize
    module procedure factorize_sp
    module procedure factorize_dp
  end interface

contains

  subroutine factorize_sp(this,info)
    use lapack, only: lapack_factorize => sgetrf
    type(lu_workspace(sp,*)), intent(inout) :: this
    integer, intent(out), optional :: info  
    include "lu_pdt.inc"
  end subroutine

  subroutine factorize_dp(this,info)
    use lapack, only: lapack_factorize => dgetrf
    type(lu_workspace(dp,*)), intent(inout) :: this
    integer, intent(out), optional :: info  
    include "lu_pdt.inc"
  end subroutine

I will note that in this usage case, the underlying LAPACK is only available in single and double precision, so declaring them up-front makes sense to me (in a perfect world, we’d also have a generic LAPACK).

I can merely suggest you have a look and participate in the j3-fortran/generics repository.

1 Like

I was concerned about type bound procedures. One should be able to pass the parameterization from the derived type to the type bound procedures. Your solution is good for independent procedures.

Thanks for suggesting the j3 repo.

The option listed by @ivanpribec is applicable to type-bound procedures also with

  1. the usual requirement the passed-object dummy argument (this per code above) be polymorphic (class(lu_workspace(sp,*)) .. given every derived type in Fortran is an extensible type per current standard and
  2. generic interface is also type-bound
type :: lu_workspace(wp,n)
    integer, kind :: wp
    integer, len :: n
    ..
  contains
    ..
    generic :: factorize => ..
  end type