Introduction

This is the third part of a series of articles that explore Object-Oriented Programming (OOP) in Fortran 2003 (F2003). The first installment introduced the OOP paradigm and three important features to OOP: inheritance, polymorphism, and information hiding. Part two covered data polymorphism, which deals with program variables that can store and operate on a variety of data types and values.

Part three introduces an F2003 feature known as parameterized derived types. Parameterized derived types allow the programmer to create derived types that take one or more values, known as parameters, to specify characteristics of the data encapsulated by the derived type. These parameters are supplied by the user of the derived type to specify the kind and/or amount of data needed by the derived type. We will first look at features and syntax of parameterized derived types. Then we will conclude our discussion with a case study that uses parameterized derived types to create general purpose matrices.

Parameterized Derived Types

F2003 permits type parameters for derived type objects. There are two varieties of type parameters: Those that must be known at compile time (called kind type parameters) and those that may not be known until runtime (called length type parameters). A derived type that uses type parameters is known as a parameterized derived type. Below is an example of a declaration of a conventional derived type object followed by a declaration of a parameterized derived type object (or simply a parameterized object):

type(matrix) :: m1               ! declare conventional derived type
type(param_matrix(8,2,2)) :: m2  ! declare parameterized derived type

Note the additional integers, or parameters, to the m2 declaration. Below are the definitions of matrix and param_matrix:

type :: matrix                ! conventional derived type definition
    real,allocatable :: m(:,:)
  end type matrix

  type :: param_matrix(k,c,r)  ! parameterized derived type definition
    integer, kind :: k 
    integer, len :: r 
    integer, len :: c 
    real(kind=k) :: m(c,r)
  end type param_matrix

Note the additional (k,c,r) next to the type definition of param_matrix. To specify a parameterized derived type, one or more type parameters are enclosed in parentheses after the type name. Next, the programmer defines each type parameter. In our example above, k, is a kind parameter. So, k is added to our derived type definition along with the kind attribute. Also note that type parameters must be declared integer. Type parameters c and r are both length type parameters because they have the len attribute. Therefore, values for c and r need not be known at compile-time as illustrated in the following code fragment.

subroutine process_matrix(columns,rows)
  integer rows, columns
  type(param_matrix(8,columns,rows)) :: m
  :
end subroutine process_matrix

The c and r type parameters for object m are not known until runtime because they are dependent on dummy arguments columns and rows. However, k is a kind type parameter. It requires a constant value. In this case, k is 8, so the kind of data that m will store is real(kind=8).

The above examples illustrate two advantages of parameterized derived types over conventional derived types. The first advantage is that you do not have to rewrite your derived type if you wish to specify a different kind for your data. You only have to specify a different value for your kind type parameter(s). The next advantage is that the size of your data can be dynamic without needing an allocatable object. Length type parameters can be used for array bounds. Otherwise, the user of the derived type would need to allocate the underlying array (or call a supplied allocation function) after they declare it. For example,

 type(matrix) :: m1              
allocate(m1%m(2,2))

Type Parameter Inquiries

The type parameters of a parameterized object are directly accessible by the programmer. However, they are read-only; not directly modifiable. For example,

type(param_matrix(8,columns,rows)) :: mat
do i = 1, mat%c
  do j = 1, mat%r
     mat%m(i,j) = mat%k
  enddo
enddo

The above code assigns the value of the kind type parameter, k, to each element in the matrix. We loop over each element using the c and r length type parameters. Because type parameters are not directly modifiable, the following code examples are not valid.

type(param_matrix(8,columns,rows)) :: mat
mat%c = 6     ! invalid
mat%r = 5     ! invalid
mat&k = 4     ! invalid

Assumed Type Parameters

In section 2, we introduced a parameterized object, m, in subroutine process_matrix(). The type of object m is param_matrix and the length parameters were set by dummy arguments columns and rows. A more common method for setting up a parameterized object in a subprogram is to pass the parameterized object as an argument into the subprogram. In order to accomplish this, the actual argument's derived type must match the dummy argument's derived type. In other words, the dummy and actual arguments must match in type, kind, and rank. When the arguments are parameterized objects, each kind and length parameter must also have the same values. For example,

subroutine process_matrix_2_2(m)
type(param_matrix(8,2,2)) :: m
:
end subroutine

subroutine process_matrix_2_3(m)
type(param_matrix(8,2,3)) :: m
:
end subroutine

type(param_matrix(8,2,2)) :: my_matrix
call process_matrix_2_2(my_matrix)          ! this is valid
call process_matrix_2_3(my_matrix)          ! this is invalid

We can legally pass the my_matrix object to subroutine process_matrix_2_2() because the kind and length type parameters are equivalent between the actual and dummy arguments. We cannot legally pass the my_matrix object to subroutine process_matrix_2_3() because the third type parameter of the actual argument does not match the third type parameter of the dummy argument. Because it would be virtually impossible to provide a process_matrix() subroutine for every combination of type parameters, F2003 permits the use of assumed type parameters. Assumed type parameters are specified with an '*' in place of a value for a length type parameter. For example,

type(param_matrix(8,*,*)) :: my_matrix

Assumed type parameters allow us to write one function for all combinations of length type parameters. Below is our revised process_matrix() subroutine:

subroutine process_matrix(m)
type(param_matrix(8,*,*)) :: m
do i = 1, mat%c
  do j = 1, mat%r
     mat%m(i,j) = mat%k
  enddo
enddo

Because kind type parameters must be known at compile-time, they are not permitted to take an assumed type parameter. However, providing a subprogram for each kind parameter is a lot more manageable than providing a subprogram for each combination of length type parameters. Moreover, we could provide a generic interface that holds an implementation for each kind type parameter. Below illustrates the use of a generic interface with our param_matrix type.

module my_matrix
type :: param_matrix(k,c,r)   
    integer, kind :: k 
    integer, len :: r 
    integer, len :: c 
    real(kind=k) :: m(c,r)
  end type param_matrix
interface process_matrix
  module procedure process_matrix_2
  module procedure process_matrix_4
  module procedure process_matrix_8
end interface process_matrix
contains
subroutine process_matrix_2(m)
type(param_matrix(2,*,*)) :: m
:
end subroutine process_matrix_2

subroutine process_matrix_4(m)
type(param_matrix(4,*,*)) :: m
:
end subroutine process_matrix_4
subroutine process_matrix_8(m)
type(param_matrix(8,*,*)) :: m
:
end subroutine process_matrix_8
end module my_matrix

use my_matrix
type(param_matrix(2,2,2)) :: m1
type(param_matrix(4,3,3)) :: m2
type(param_matrix(8,4,4)) :: m3
call process_matrix(m1)
call process_matrix(m2)
call process_matrix(m3)
end

The above program illustrates how we can create one interface, called process_matrix(), that operates on a variety of kind and length type parameters.

One restriction to note on assumed type parameters is that they may not be used with objects that have the allocatable or pointer attribute. The following examples are illegal in Fortran:

subroutine dup_matrix(m,n)
type(param_matrix(8,*,*)),allocatable :: m    ! invalid
type(param_matrix(8,*,*)),pointer :: n        ! invalid
:
end subroutine dup_matrix

We can accomplish the above example using Deferred Type Parameters which is the topic of the next section.

Deferred Type Parameters

In the previous section, we showed how assumed type parameters act as place holders for length type parameters. These place holders, designated with an '*', tell the compiler that the length type parameter values are not known until the program calls the host function or subroutine. Deferred type parameters also act as place holders for length type parameters. These place holders, designated with a ':', tell the compiler that the length type parameter values are not known until their host object is allocated or assigned to a pointer. Below are examples of allocation and pointer assignment using deferred type parameters.

type(param_matrix(4,:,:)), allocatable :: m1
type(param_matrix(4,:,:)), pointer :: ptr
type(param_matrix(4,2,2)), target :: m2
type(param_matrix(4,:,:), allocatable :: m3

allocate(type(param_matrix(4,2,2))::m1)          ! typed allocation
ptr => m2                                        ! pointer assignment
allocate(m3, source=ptr)                         ! sourced allocation

We set the values of the length type parameters for m1 using typed allocation. Values for ptr's length type parameters are set after associating ptr with m2. In the sourced allocation, m3 inherits its length type parameters from ptr.

Deferred type parameters may only be used with allocatable and pointer objects. As mentioned in the previous section, assumed type parameters may not be used with allocatable and pointer objects. Therefore, you must use deferred type parameters for allocatable and pointer dummy arguments if your subprogram requires a parameterized object with unknown length type parameters. Below is the correct implementation of dup_matrix() introduced in the previous section:

subroutine dup_matrix(m,n)
type(param_matrix(8,:,:)),allocatable :: m    ! valid
type(param_matrix(8,:,:)),pointer :: n        ! valid
:
end subroutine dup_matrix

Default Type Parameters

You may optionally define a default value for each type parameter. Each default value must be known at compile-time. For example,

type :: param_matrix(k,c,r)   
    integer, kind :: k = 4 
    integer, len :: r = 1 
    integer, len :: c = 1
    real(kind=k) :: m(c,r)
  end type param_matrix

When default values are specified, you may specify all, some, or none of the type parameters when declaring an instance of the parameterized derived type.

type(param_matrix) :: m1        ! k=4, c=1, r=1
type(param_matrix(8)) :: m2     ! k=8, c=1, r=1
type(param_matrix(8,2)) :: m3   ! k=8, c=2, r=1
type(param_matrix(2,2,3)) :: m4 ! k=2, c=2, r=3

Type Parameter Names

Up to this point, we specified our type parameters in the order that they appear in the derived type definition. For example, the (2,2,3) in type(param_matrix(2,2,3)) maps to (k,c,r) in the param_matrix type definition. In the previous section, we introduced default type parameters. Let us say that we want to use the default value for type parameter c but specify values for k and r. We would not be able to accomplish this if we must specify our parameters in the order that they appear. F2003 alleviates this restriction by allowing the programmer to specify type parameters by their name. For example,

type :: param_matrix(k,c,r)   
    integer, kind :: k = 4 
    integer, len :: r = 1 
    integer, len :: c = 1
    real(kind=k) :: m(c,r)
end type param_matrix

type(param_matrix(k=2,c=2,r=3)) :: m1 ! k=2, c=2, r=3
type(param_matrix(c=3,k=2,r=2)) :: m2 ! k=2, c=3, r=2
type(param_matrix(k=8,r=3)) :: m3     ! k=8, c=1, r=3
type(param_matrix(r=2,c=3)) :: m4     ! k=4, c=3, r=2

In the example above, we specify our type parameters using an assignment to the type parameter name. Note that the parameter name is on the left hand side and the parameter value is on the right hand side of the equal sign. This allows us to specify values for our type parameters out of order, as shown with the m2 object. Because we used default type parameters, we can leave "holes" in our specification as shown in the m3 and m4 objects.

Assumed and deferred type parameters may also be used with type names:

type(param_matrix(k=2,r=*,c=*)) :: m1
type(param_matrix(c=:,k=2,r=:)), pointer :: m2

Inheritance and Parameterized Derived Types

When we extend a parameterized derived type, we inherit all type parameters from our parent type(s). For example,

type :: amatrix(k,c,r)   
    integer, kind :: k = 4 
    integer, len :: r = 1 
    integer, len :: c = 1
end type amatrix

type, extends(amatrix) :: rmatrix
    real(kind=k) :: m(c,r)
end type rmatrix

type, extends(amatrix)::imatrix
    integer(kind=k) :: m(c,r)
end type imatrix

The rmatrix and imatrix derived types do not specify any type parameters, however, they inherit type parameters k,c,r from amatrix. Below are examples of rmatrix and imatrix declarations:

type(rmatrix(8,2,2)) :: m1
type(imatrix(c=2,r=2)) :: m2

A child object that inherits type parameters may also specify their own type parameters. However, names of type parameters specified in the child may not be the same as names specified in the parent. For example,

type :: amatrix(k,c,r)   
    integer, kind :: k = 4 
    integer, len :: r = 1 
    integer, len :: c = 1
end type amatrix

type, extends(amatrix) :: r_key_matrix(k)     ! invalid
  integer, kind :: k
  real(kind=k) :: m(c,r)
end type rmatrix

type, extends(amatrix)::i_key_matrix(key)     ! valid
  integer, kind :: key  
  integer(kind=k) :: m(c,r)
end type imatrix

Below are examples of declaring child parameterized objects with inherited type parameters:

type(i_key_matrix(4,2,2,1)) :: m1       ! k=4, c=2, r=2, key=1
type(i_key_matrix(key=2,k=8)) :: m2     ! k=8, c=1, r=1, key=2

Note that the parent type parameters are specified before the child type parameters in m1. If you use type parameter names, as we did in m2, then child and parent type parameters may be specified in any order.

Case Study: A General Purpose Matrix

Now that we have introduced parameterized objects, let us take a look at how they might be used in an application. For this case study, we will create a general purpose matrix. The parameterized derived type that we create can operate on a variety of data types as well as a variety of data kinds and lengths. Moreover, we will be able to use the powerful parameterized derived type syntax to create matrices. Please note that the examples in this section require version 13.10 or higher of the pgfortran compiler.

We will first create our base type for our matrix inside a module called matrix:

module matrix
type :: base_matrix(k,c,r)
    integer, kind :: k = 4
    integer, len :: c = 1
    integer, len :: r = 1
end type base_matrix
:
end module matrix

Our base type has three type parameters: k,c, and r. The k parameter is our kind parameter. The c parameter specifies the number of columns in our matrix. The r parameter specifies the number of rows in our matrix.

Note that the type parameters are publically visible to our users (i.e., they are not declared private). One advantage to F2003 is that type parameters are read-only. We can expose them to the user and maintain some degree of information hiding because users cannot directly modify type parameters. In other programming languages, like C++, we would need to declare these data components private (or protected) and add access routines in order to maintain the read-only behavior. Of course if we want nice descriptive access routines for each type parameter, we could add them. For example, let us create an access routine for our k parameter.

We first create a generic interface called getKind:

interface getKind
  module procedure getKind4
  module procedure getKind8
end interface getKind

Next, we create our module procedures. Note that our getKind interface has two module procedures, getKind4 and getKind8. The getKind4 and getKind8 module procedures operate on base_matrix(4,*,*) and base_matrix(8,*,*) types respectively:

  function getKind4(this) result(rslt)
   class(base_matrix(4,*,*)) :: this
   integer :: rslt
   rslt = this%k
  end function getKind4

  function getKind8(this) result(rslt)
   class(base_matrix(8,*,*)) :: this
   integer :: rslt
   rslt = this%k
  end function getKind8

Each function operates on a different value for our kind parameter, k. Because parameters c and r are length type parameters, they can be declared assumed ('*'). If we want to support other kind values, say kind=2, then we can create a getKind2 module procedure with a this argument declared class(base_matrix(2,*,*)). We can also create descriptive access routines for parameters c and r using the same approach as getKind.

Now, let us move onto the actual matrix object type. Because we want our matrix to operate on a variety of data types, we can use an unlimited polymorphic pointer for our matrix data. Below is our type definition:

type, extends(base_matrix) ::  adj_matrix
  private
    class(*), pointer :: m(:,:) => null()
end type adj_matrix

We refer to our child type as adj_matrix which is short for "adjustable matrix". This type has a private data component called m which holds our matrix data.

Now we can create our type constructors using a generic interface called adj_matrix. Like what we did with the getKind generic interface above, we create module procedures for kind=4 and kind=8 data as illustrated below:

interface adj_matrix
   module procedure construct_4   ! kind=4 constructor
   module procedure construct_8   ! kind=8 constructor
end interface adj_matrix
:
function construct_4(k,c,r) result(mat)
     integer(4) :: k
     integer :: c
     integer :: r
     class(adj_matrix(4,:,:)),allocatable :: mat

     allocate(adj_matrix(4,c,r)::mat)

  end function construct_4

  function construct_8(k,c,r) result(mat)
     integer(8) :: k
     integer :: c
     integer :: r
     class(adj_matrix(8,:,:)),allocatable :: mat

     allocate(adj_matrix(8,c,r)::mat)

  end function construct_8

Similar to getKind4() and getKind8() above, the only difference between construct_4() and construct_8() is the value for kind parameter k in the declaration of mat. For our constructor functions, we take three arguments, k, c, and r which correspond to type parameters k, c, and r. Note that our result, mat, is declared allocatable. We construct result object, mat, with a typed allocation statement. With allocatable objects, we can use deferred type parameters when we use adj_matrix objects in a program.

Below is a sample program which covers what we have implemented up to this point:

program adj1
  use matrix
  implicit none
  integer(8):: i,j,k
  type(adj_matrix(8,:,:)),allocatable :: adj
  type(adj_matrix(4,:,:)),allocatable :: adj2

  adj = adj_matrix(INT(8,8),2,4)
  adj2 = adj_matrix(4,16,32)
  print *, 'adj%k=',getKind(adj)
  print *, 'adj%c=',getColumns(adj)
  print *, 'adj%r=',getRows(adj)
  print *, 'adj2%k=',getKind(adj2)
  print *, 'adj2%c=',getColumns(adj2)
  print *, 'adj2%r=',getRows(adj2)
end program adj1

In the program above, we declare two matrices, adj and adj2. As shown in the adj_matrix generic interface above, there are two module procedures called construct_4 and construct_8. The compiler determines which constructor function to call based on the first argument. Therefore, we need to promote our 8 in the adj construction to kind=8 in order to get the correct constructor function. We accomplish this promotion using the INT intrinsic. If we fail to promote the 8 in the adj construction, the compiler will issue an error message similar to the following:

PGF90-S-0099-Illegal use of derived type (adj1.f90: 107)
  0 inform,   0 warnings,   1 severes, 0 fatal for adj1

Below is a compile and run of the above program. It is also available for download.

% pgfortran -V -Mallocatable=03 adj1.f90

pgfortran 13.10 64-bit target on x86-64 Linux -tp sandybridge 
The Portland Group - PGI Compilers and Tools
Copyright (c) 2013, NVIDIA CORPORATION.  All rights reserved.
% ./a.out
 adj%k=            8
 adj%c=            2
 adj%r=            4
 adj2%k=            4
 adj2%c=           16
 adj2%r=           32

The above program prints values of each type parameter. Also note the use of the ‑Mallocatable=03 compiler switch. This switch tells the compiler to use F2003 style allocation. F2003 style allocation includes automatic allocation of objects on the left hand side of an assignment. Our program assumes F2003 style allocation in the program lines adj=adj_matrix(INT(8,8),2,4) and adj2=adj_matrix(4,16,32). If we did not use this switch, our program would cause a runtime segmentation fault.

To eliminate the ‑Mallocatable=03 switch requirement, we can define our own assignment operator that mimics the behavior of the F2003 style allocation. Below is a generic interface followed by the module procedures. The complete program is available for download as well.

interface assignment(=)
   module procedure m2m4          ! assign kind=4 matrix 
   module procedure m2m8          ! assign kind=8 matrix 
end interface assignment(=)
:
subroutine m2m4(d,s)
   class(adj_matrix(4,:,:)),allocatable :: d
   class(adj_matrix(4,*,*)) :: s

   if (allocated(d)) deallocate(d)
   allocate(d,source=s)
 end subroutine

 subroutine m2m8(d,s)
   type(adj_matrix(8,:,:)),allocatable :: d
   type(adj_matrix(8,*,*)) :: s

   if (allocated(d)) deallocate(d)
   allocate(d,source=s)
 end subroutine

The above functions m2m4 and m2m8 take two matrices, d and s as dummy arguments. The d argument represents the left hand side of the assignment and the s argument represents the right hand side of the assignment. In the case of adj=adj_matrix(INT(8,8),2,4), d=adj and s=adj_matrix(INT(8,8),2,4). We deallocate d if it is already allocated to prevent memory leaks. Next, we use a sourced allocation statement to clone the s matrix. After incorporating our user defined assignment, we can compile our program without the ‑Mallocatable=03 switch:

% pgfortran -V adj2.f90

pgfortran 13.10 64-bit target on x86-64 Linux -tp sandybridge 
The Portland Group - PGI Compilers and Tools
Copyright (c) 2013, NVIDIA CORPORATION.  All rights reserved.
% ./a.out
 adj%k=            8
 adj%c=            2
 adj%r=            4
 adj2%k=            4
 adj2%c=           16
 adj2%r=           32

Now we need a way to initialize our matrix. One possibility is to use our assignment operator for initializing our matrix. Since a matrix is essentially a two dimensional array, having an assignment by an array would be useful. For example,

interface assignment(=)
   module procedure a2m4          ! assign kind=4 array  
   module procedure a2m8          ! assign kind=8 array  
end interface assignment(=)
:
subroutine a2m4(d,s)
   class(adj_matrix(4,:,:)),allocatable :: d
   class(*),dimension(:,:) :: s

   if (allocated(d)) deallocate(d)
   allocate(adj_matrix(4,size(s,1),size(s,2))::d)
   allocate(d%m(size(s,1),size(s,2)),source=s)
 end subroutine a2m4

 subroutine a2m8(d,s)
   class(adj_matrix(8,:,:)),allocatable :: d
   class(*),dimension(:,:) :: s

   if (allocated(d)) deallocate(d)
   allocate(adj_matrix(8,size(s,1),size(s,2))::d)
   allocate(d%m(size(s,1),size(2,2)),source=s)
 end subroutine a2m8

Again, we use a sourced allocation, but this time we use it to construct our matrix data component, m. Also note that argument s is a two dimensional unlimited polymorphic object. These subroutines can work on any type; whether it's an intrinsic data type, like real, or a (parameterized) derived type.

Let us now add a similar method for retrieving data. The code below shows how we can add an assignment to an array.

interface assignment(=)
   module procedure m2a4          ! assign kind=4 matrix to array
   module procedure m2a8          ! assign kind=8 matrix to array
end interface assignment(=)
:
subroutine m2a8(a,this)
class(adj_matrix(8,*,*)) :: this
class(*),allocatable :: a(:,:)
  if (allocated(a)) deallocate(a)
  allocate(a(size(this%m,1),size(this%m,2)),source=this%m)
 end subroutine m2a8

 subroutine m2a4(a,this)
 class(adj_matrix(4,*,*)) :: this
 class(*),allocatable :: a(:,:)
   if (allocated(a)) deallocate(a)
   allocate(a(size(this%m,1),size(this%m,2)),source=this%m)
 end subroutine m2a4

These subroutines also use a sourced allocation statement. However, this time the result is a two dimensional unlimited polymorphic object. Below is a program that demonstrates the initialization and retrieval features. The complete program is available for download as well.

 program adj3

  use matrix
  implicit none
  integer(8) :: i,j,k
  type(adj_matrix(8,:,:)),allocatable :: adj
  real(8) :: a(2,3)
  real(8),allocatable :: b(:,:)

  adj = adj_matrix(INT(8,8),2,4)
  
  k = 1
  do i=1,2
   do j=1, 3
    a(i,j) = k
    k = k + 1
   enddo
  enddo

  adj = a
  b = adj

  print *, b

end program adj3

The above program initializes a two dimensional array, a, and assigns it to our matrix adj. Next, we assign adj to array b. Then we print each element of b. Note that b is an allocatable array. Also note that we automatically allocate b with our user defined assign operator. In this case, the allocation occurs in the m2a8() subroutine.

Below is a compile and run of our program:

% pgfortran -V adj3.f90

pgfortran Rel 13.10 64-bit target on x86-64 Linux -tp sandybridge 
The Portland Group - PGI Compilers and Tools
Copyright (c) 2013, NVIDIA CORPORATION.  All rights reserved.
% ./a.out
    1.000000000000000         4.000000000000000         2.000000000000000      
    5.000000000000000         3.000000000000000         6.000000000000000    

Some other procedures that you could add to the adj_matrix type include a function that retrieves a single element from the matrix, a subroutine that sets a single element in the matrix, and a subroutine that prints the matrix. For the print subroutine, you could use the F2003 Derived Type I/O feature. We will discuss Derived Type I/O in Part 4 of this series.

Conclusion

Data polymorphism deals with program variables that can store and operate on a variety of data types and values. The simplest form of data polymorphism in F2003 occurs with unlimited polymorphic objects (i.e., objects declared class(*)). Another form of data polymorphism in F2003 occurs with parameterized derived types. Parameterized derived types allow the programmer to create derived types that take one or more values, known as parameters, to specify characteristics of the data encapsulated by the derived type. These characteristics can specify the precision (or kind) of data and the amount (or length) of data that the object processes. In other words, parameterized derived types offer two distinct advantages over conventional derived types: Parameterized derived types provide a way to specify variable length data without requiring an explicit dynamic allocation. Parameterized derived types also permit code reusability because they do not require a rewrite in order to support a different kind of data.

  • ©2013 NVIDIA Corporation
Click me
Cookie Consent

This site uses cookies to store information on your computer. See our cookie policy for further details on how to block cookies.

X