Skip to content

Parameterized derived types in Fortran - introduction

User-defined data types in Fortran may have parameters which control certain aspects of their definition. In this post we look at what these parameterized types are, how they are used and what benefits they may offer to the programmer.

As Fortran programmers, we're used to the idea of type parameters for data objects. For example, we may specify a kind parameter for a real or character variable:

use, intrinsic :: iso_fortran_env, only : real32, real64
real(kind=real32) small
real(kind=rea64) big
character(kind=SELECTED_CHAR_KIND('ISO_10646')) ucs_name

Character variables have a length of one by default, but in declaring such a variable we may specify a different value for the length parameter:

character(len=32) name

The length parameter of a character variable may be deferred, letting us change a variable's length over time:

character(len=:), allocatable :: name
name = "Lassie"
print '("My name has ",I0," letters")', LEN(name)
name = "Spot"
print '("My new name has ",I0," letters")', LEN(name)
end

Defining a parameterized derived type

Fortran 2003 introduced similar type parameter concepts to the user-definable derived types. Before this language revision we could specify the type parameters of the components of a derived type, such as in

type point_type
  real(kind=real64) x, y
  character(len=12) label
end type

type(point_type) point

Parameterized derived types are defined in a similar way but with additional detail:

type point_type(point_kind, label_len)
  integer, kind :: point_kind
  integer, len :: label_len
  real(kind=point_kind) x, y
  character(len=label_len) label
end type

Here, point_type has two parameters, point_kind and label_len. The line integer, kind :: point_kind says that the parameter point_kind is a kind parameter and integer, len :: label_len says that label_len is a length parameter.

A kind parameter for a derived type object is conceptually the same as for an intrinsic object: its value is a constant and is suitable to be used as a kind parameter for that type's component. Length parameters have the freedom to be not constant. Further, although the type parameters are called "kind" and "length", their use doesn't have to match that use. For example, a kind type parameter may be used to specify a length or shape of a component:

type point_type(dimension, label_len)
  integer, kind :: dimension
  integer, len :: label_len
  real location(dimension)
  character(len=label_len) label
end type

Much as type parameters of a derived type may be used to specify parameters for intrinsic type components, components of a derived type may also be parameterized.

Finally, type parameters may have default values:

type point_type(dimension)
  integer, len :: dimension = 2
  real x(dimension)
end type

Declaring and using a parameterized derived type

Basic syntax

To declare a data object as being of a parameterized derived type we use a similar syntax for a non-parameterized type, but may add values for the type parameters in the following way:

type mytype(n)
  integer, len :: n=1
  real a(n)
end type

type(mytype) x        ! Using default parameter value 1
type(mytype(2)) y     ! Parameter value 2

print '("Component of x has size ", I0)', SIZE(x%a)
print '("Component of y has size ", I0)', SIZE(y%a)

end

Without a default value for the type parameter, the corresponding value must be provided in a declaration. In the above example, the declaration for x would not be allowed if n had no default value (with integer, len :: n).

Deferred length parameters

For pointer and allocatable objects, length type parameters may be deferred, as with the character example above:

type mytype(n, m)
  integer, len :: n=1
  integer, kind :: m
  real a(n)
end type

type(mytype(:,2)), allocatable :: x
type(mytype(m=2,n=:)), pointer :: y
type(mytype(m=2)), target :: z

allocate(x, mold=z)
y=>z

print '("Component of x has size ", I0)', SIZE(x%a)
print '("Component of y has size ", I0)', SIZE(y%a)

end

The deferred type parameter n of x and y take on the values of z's non-deferred type parameter. For x this happens in the allocation (with the mold= specifier) and for y on pointer assignment. Setting of the type parameter may also occur through assignment or sourced allocation or allocation with a type specifier.

In the example above we also see how to specify multiple parameter values, or just those without defaults.

Type parameter inquiry

In the examples above with a parameterized derived type object, we saw the effect of the parameter value on the components. For an array component where the number of elements depends on a parameter, we looked at the size of the array.

We can also directly query the type parameters:

type mytype(n)
  integer, len :: n
end type

type(mytype(3)) x

print '("x has length parameter ", I0)', x%n

end

Although x%n looks like a component access, the type parameter isn't a component. In particular, the type parameter cannot be set in this way:

type mytype(n)
  integer, len :: n
end type

type(mytype(:)), allocatable :: x

! Incorrectly try to define the length parameter:
x%n = 3   ! This won't work

! Instead we can allocate:
allocate(mytype(3) :: x)

end

Parameterized derived types as procedure arguments

We can write our own procedures which accept parameterized derived types. What we can do in the procedure, and how we declare the arguments, depends on whether the argument has kind parameters or not.

Whenever we reference a procedure with a parameterized type argument we must have an explicit interface for the procedure available.

Kind type parameters

As with intrinsic types, kind type parameters for a derived type cannot be assumed or deferred, and must be constant expressions. When we are writing a procedure taking an argument with a kind type parameter we must have an exact match:

type mytype(n)
  integer, kind :: n
end type mytype

interface sub
  procedure sub1, sub2
end interface

type(mytype(1)) x
type(mytype(2)) y

call sub(x)
call sub(y)

contains

  subroutine sub1(z)
    type(mytype(1)) z
    print '("Inside sub1")'
  end subroutine sub1

  subroutine sub2(z)
    type(mytype(2)) z
    print '("Inside sub2")'
  end subroutine sub2

end

As with intrinsic types, kind type parameters for a derived type are considered, for generics, when deciding whether arguments are distinguishable.

Length type parameters

Arguments with length type parameters can similarly have these parameters given by specification expressions (which needn't be constant expressions). However, length type parameters are not considered in argument distinguishability for generics.

Additionally, dummy arguments may have length type parameters assumed from the corresponding actual argument, using * as the type parameter specification:

type mytype(n, m)
  integer, len :: n
  integer, kind :: m
  real a(n)
end type

type(mytype(5,2)) x

call sub(x)

contains

  subroutine sub(y)
    type(mytype(*,2)) y
    print '("Component of dummy argument has size ", I0)', SIZE(y%a)
  end subroutine

end

Kind type parameters may not be assumed.

A dummy argument may have some type parameters assumed and some deferred. In allocating such an object with deferred type parameter we can again use a * to refer to the value of any assumed type parameter:

type mytype(n, m)
  integer, len :: n, m
  real a(n)
end type

type(mytype(1,:)), allocatable :: x

call sub(x)
print '("x has type parameters ", I0, " and ", I0)', x%n, x%m

contains

  subroutine sub(y)
    type(mytype(*,:)), allocatable, intent(out) :: y
    allocate(mytype(*,2) :: y)
  end subroutine

end

Comparing parameterized and non-parameterized derived types

Up to here, we've seen how to use parameterized types. However, we should also think about when or why to use them.

A natural comparison to make is with derived types which have an array component whose size is not know when compiling, or may vary during the program's running. In a non-parameterized type we would likely choose to use an allocatable array component.

Using an allocatable array component creates additional overhead, is such ways as in writing the code. For example, we'll need to provide a separate step to set up the allocation of the component and provide additional checks to ensure that the component is allocated and of the expected size. For arrays of derived type with array component this overhead can be quite significant.

Allocatable components also have limitations in their use. If we have a reference such as array(:)%component then the component cannot be allocatable. It may, however, have a length parameter:

implicit none

type works(n)
  integer, len :: n
  character(len=n) :: name
end type

type fails
  character(len=:), allocatable :: name
end type

type(works(5)) dog(5)
type(fails) cat(5)

integer i

call set_names_fixed(dog%name)      ! Allowed
call set_names_alloc(cat%name)      ! Not allowed

do i=1,SIZE(cat)
  call set_name_alloc(cat(i)%name)  ! Alternative
end do

end

In a later blog post we'll see an example comparing approaches using a derived type with and without parameters. This will look at performance implications as well as the coding overhead.

Of significant note, however, is that parameterized derived types complicate the implementation of a Fortran processor significantly. Being a relatively new feature also, using parameterized types can be a frustrating experience at times, with compiler bugs being a potential problem.

Conclusion

In this post we've seen what parameterized derived types, introduced into Fortran in the 2003 revision, are. We've seen how they can be defined and how to create objects of their type. They may have kind or length parameters which relate to the kind of length parameters of the intrinsic types we've seen before.

The post showed how to use parameterized types as arguments and how to query their properties. We've seen some of the potential advantages in code clarity compared with using allocatable components but also some of their disadvantages.

A follow-up post will look at how using types with parameters may affect the performance of a Fortran program and how to balance any slowing against the benefits to quality of the code using them.

Please contact us for advice using parameterized derived types or to let us know about your experiences, good or bad, with them.