Derived Types#
As discussed previously in Variables, there are five built-in data types in Fortran. A derived type is a special form of data type that can encapsulate other built-in types as well as other derived types. It could be considered equivalent to struct in the C and C++ programming languages.
A quick take on derived types#
Here’s an example of a basic derived type:
type :: t_pair
  integer :: i
  real :: x
end type
The syntax to create a variable of type t_pair and access its members is:
! Declare
type(t_pair) :: pair
! Initialize
pair%i = 1
pair%x = 0.5
The percentage symbol
%is used to access the members of a derived type.
In the above snippet, we declared an instance of a derived type and initialized its members explicitly. You can also initialize derived type members by invoking the derived type constructor.
Example using the derived type constructor:
pair = t_pair(1, 0.5)      ! Initialize with positional arguments
pair = t_pair(i=1, x=0.5)  ! Initialize with keyword arguments
pair = t_pair(x=0.5, i=1)  ! Keyword arguments can go in any order
Example with default initialization:
type :: t_pair
  integer :: i = 1
  real :: x = 0.5
end type
type(t_pair) :: pair
pair = t_pair()       ! pair%i is 1, pair%x is 0.5
pair = t_pair(i=2)    ! pair%i is 2, pair%x is 0.5
pair = t_pair(x=2.7)  ! pair%i is 1, pair%x is 2.7
Derived types in detail#
The full syntax of a derived type with all optional properties is presented below:
type [,attribute-list] :: name [(parameterized-declaration-list)]
  [parameterized-definition-statements]
  [private statement or sequence statement]
  [member-variables]
contains
  [type-bound-procedures]
end type
Options to declare a derived type#
attribute-list may refer to the following:
- access-type that is either - publicor- private
- bind(c)offers interoperability with C programming language
- extends(parent- ), where parent is the name of a previously declared derived type from which the current derived type will inherit all its members and functionality
- abstract– an object oriented feature that is covered in the advanced programming tutorial
If the attribute
bind(c)or the statementsequenceis used, then a derived type cannot have the attributeextendsand vice versa.
The sequence attribute may be used only to declare that the following members should be accessed in the same order as they are defined within the derived type.
Example with sequence:
type :: t_pair
  sequence
  integer :: i
  real :: x
end type
! Initialize
type(t_pair) :: pair
pair = t_pair(1, 0.5)
The use of the statement
sequencepresupposes that the data types defined below are neither ofallocatablenor ofpointertype. Furthermore, it does not imply that these data types will be stored in memory in any particular form, i.e., there is no relation to thecontiguousattribute.
The access-type attributes public and private, if used, declare that all member-variables declared below will be automatically assigned the attribute accordingly.
The attribute bind(c) is used to achieve compatibility between Fortran’s derived type and C’s struct.
Example with bind(c):
module f_to_c
  use iso_c_bindings, only: c_int
  implicit none
  type, bind(c) :: f_type
    integer(c_int) :: i
  end type
end module f_to_c
matches the following C struct type:
struct c_struct {
  int i;
};
A fortran derived type with the attribute
bind(c)cannot have thesequenceandextendsattributes. Furthermore it cannot contain any Fortranpointerorallocatabletypes.
parameterized-declaration-list is an optional feature. If used, then the parameters must be listed in place of [parameterized-definition-statements] and must be either len or kind parameters or both.
Example of a derived type with parameterized-declaration-list and with the attribute public:
module m_matrix
 implicit none
 private
 type, public :: t_matrix(rows, cols, k)
   integer, len :: rows, cols
   integer, kind :: k = kind(0.0)
   real(kind=k), dimension(rows, cols) :: values
 end type
end module m_matrix
program test_matrix
 use m_matrix
 implicit none
 type(t_matrix(rows=5, cols=5)) :: m
end program test_matrix
In this example the parameter
khas already been assigned a default value ofkind(0.0)(single-precision floating-point). Therefore, it can be omitted, as is the case here in the declaration inside the main program.
By default, derived types and their members are public. However, in this example, the attribute
privateis used at the beginning of the module. Therefore, everything within the module will be by defaultprivateunless explicitly declared aspublic. If the typet_matrixwas not given the attributepublicin the above example, then the compiler would throw an error insideprogram test.
The attribute extends was added in the F2003 standard and introduces an important feature of the object oriented paradigm (OOP), namely inheritance. It allows code reusability by letting child types derive from extensible parent types: type, extends(parent) :: child. Here, child inherits all the members and functionality from type :: parent.
Example with the attribute extends:
module m_employee
  implicit none
  private
  public t_date, t_address, t_person, t_employee
  ! Note another way of using the public attribute:
  ! gathering all public data types in one place.
  type :: t_date
    integer :: year, month, day
  end type
  type :: t_address
    character(len=:), allocatable :: city, road_name
    integer :: house_number
  end type
  type, extends(t_address) :: t_person
    character(len=:), allocatable :: first_name, last_name, e_mail
  end type
  type, extends(t_person)  :: t_employee
    type(t_date) :: hired_date
    character(len=:), allocatable :: position
    real :: monthly_salary
  end type
end module m_employee
program test_employee
  use m_employee
  implicit none
  type(t_employee) :: employee
  ! Initialization
  ! t_employee has access to type(t_date) members not because of extends
  ! but because a type(t_date) was declared within t_employee.
  employee%hired_date%year  = 2020
  employee%hired_date%month = 1
  employee%hired_date%day   = 20
  ! t_employee has access to t_person, and inherits its members due to extends.
  employee%first_name = 'John'
  employee%last_name  = 'Doe'
  ! t_employee has access to t_address, because it inherits from t_person,
  ! which in return inherits from t_address.
  employee%city         = 'London'
  employee%road_name    = 'BigBen'
  employee%house_number = 1
  ! t_employee has access to its defined members.
  employee%position       = 'Intern'
  employee%monthly_salary = 0.0
end program test_employee
Options to declare members of a derived type#
[member-variables] refers to the declaration of all the member data types. These data types can be of any built-in data type, and/or of other derived types, as already showcased in the above examples. However, member-variables can have their own extensive syntax, in form of:
type [,member-attributes] :: name[attr-dependent-spec][init]
type: any built-in type or other derived type
member-attributes (optional):
- publicor- privateaccess attributes
- allocatablewith or without- dimensionto specify a dynamic array
- pointer,- codimension,- contiguous,- volatile,- asynchronous
Examples of common cases:
type :: t_example
  ! 1st case: simple built-in type with access attribute and [init]
  integer, private :: i = 0
  ! private hides it from use outside of the t_example's scope.
  ! The default initialization [=0] is the [init] part.
  ! 2nd case: dynamic 1-D array
  real, allocatable, dimension(:) :: x
  ! the same as
  real, allocatable :: x(:)
  ! This parentheses' usage implies dimension(:) and is one of the possible [attr-dependent-spec].
end type
The following attributes:
pointer,codimension,contiguous,volatile,asynchronousare advanced features that will not be addressed in the Quickstart tutorial. However, they are presented here, in order for the readers to know that these features do exist and be able to recognize them. These features will be covered in detail in the upcoming Advanced programing mini-book.
Type-bound procedures#
A derived type can contain functions or subroutines that are bound to it. We’ll refer to them as type-bound procedures. Type-bound procedures follow the contains statement that, in turn, follows all member variable declarations.
It is impossible to describe type-bound procedures in full without delving into OOP features of modern Fortran. For now we’ll focus on a simple example to show their basic use.
Here’s an example of a derived type with a basic type-bound procedure:
module m_shapes
  implicit none
  private
  public t_square
  type :: t_square
  real :: side
  contains
    procedure :: area  ! procedure declaration
  end type
contains
  ! Procedure definition
  real function area(self) result(res)
    class(t_square), intent(in) :: self
    res = self%side**2
  end function
end module m_shapes
program main
  use m_shapes
  implicit none
  ! Variables' declaration
  type(t_square) :: sq
  real :: x, side
  ! Variables' initialization
  side = 0.5
  sq%side = side
  x = sq%area()
  ! self does not appear here, it has been passed implicitly
  ! Do stuff with x...
end program main
What is new:
- selfis an arbitrary name that we chose to represent the instance of the derived type- t_squareinside the type-bound function. This allows us to access its members and to automatically pass it as an argument when we invoke a type-bound procedure.
- We now use - class(t_square)instead of- type(t_square)in the interface of the- areafunction. This allows us to invoke the- areafunction with any derived type that extends- t_square. The keyword- classintroduces the OOP feature polymorphism.
In the above example, the type-bound procedure area is defined as a function and can be invoked only in an expression, for example x = sq%area() or print *, sq%area(). If you define it instead as a subroutine, you can invoke it from its own call statement:
! Change within module
contains
  subroutine area(self, x)
    class(t_square), intent(in) :: self
    real, intent(out) :: x
    x = self%side**2
  end subroutine
! ...
! Change within main program
call sq%area(x)
! Do stuff with x...
In contrast to the example with the type-bound function, we now have two arguments:
- class(t_square), intent(in) :: self– the instance of the derived type itself
- real, intent(out) :: x– used to store the calculated area and return to the caller
