Fortran/OOP in Fortran

From Wikibooks, open books for an open world
Jump to navigation Jump to search

Object-oriented programming

Module

Overview

Data can be gathered in modules. The general form is given by

module <name>
  <use statements>
  <declarations>
contains
  <subroutines and functions>
end module <name>

Data access

There are three possible access properties: public, private, protected.

  • public: Outside code has read and write access.
  • private: Outside code has no access.
  • public, protected: Outside code has read access.

Using module in other code

One can include the module's public data in outside code. There are three ways.

  • use <moduleName>: includes all public data and methods
  • use <moduleName>, <renames>: includes all public data and methods, but renames some public data or methods
  • use <moduleName>, only : <subset>: includes only some public data and methods

Example

General overview
module test_mod
  implicit none
  private                                   ! all data is by default private
  real :: x,y
  public :: print_coords, set_coords        ! these procedures are set public

contains
  subroutine print_coords
    implicit none
    print *, "x:",x,"y:",y
  end subroutine print_coords

  subroutine set_coords( new_x, new_y )
    implicit none
    real, intent(in) :: new_x, new_y
    x = new_x
    y = new_y
  end subroutine set_coords
end module test_mod

program main
  use test_mod                              ! import the "test_mod" module
  implicit none

  call set_coords( 1., 1. )                 ! call the public procedure from test_mod
  call print_coords

end program main
Data access
module test_module
  implicit none
  private
  integer, public :: a=1
  integer, public, protected :: b=1
  integer, private :: c=1
end module test_module

program main
  use test_module

  ! accessing public object works
  print *, a

  ! editing public object works
  a = 2

  ! accessing protected object works
  print *, b

  ! editing protected object does not work
  !b = 2 <- ERROR

  ! accessing private object does not work
  !print *, c <- ERROR

  ! editing private object does not work
  !c = 2 <- ERROR

end program main
Using modules
module test_module
  implicit none
  private
  integer, public :: a=1
  integer, public, protected :: b=1
  integer, private :: c=1
end module test_module

!> import all public data of test_module
program main
  use test_module

  print *, a, b
end program main

!> import all data, and rename
program main
  use test_module, better_name => a

  ! new name use available
  print *, better_name

  ! old name is not available anymore
  !print *, a  <- ERROR
end program main

!> import only a subset of the public data
program main
  use test_module, only : a

  ! only a is loaded
  print *, a

  ! b is not loaded
  !print *, b  <- ERROR
end program main

Submodule

Modules can be extended using submodules. Multiple advantages arise

  • splitting of large modules
  • splitting of interface definitions and implementations such that dependent modules do not need to be recompiled if the implementations change
  • two modules need data from each other.

Example

Splitting of definitions and implementations
!> simple module about circles
module circle_mod
  implicit none
  private
  public :: area, radius

  real            :: radius
  real, parameter :: PI = 3.1415

  interface                              ! interface block needed. each function implemented via submodule needs an entry here.
    module function area()               ! important note the "module" keyword
      real :: area
    end function 
  end interface
end module 

submodule (circle_mod) circle_subm       ! submodule (parent_mod) child_mod
contains
  module function area()                 ! again "module" keyword
    area = PI*radius**2
  end function 
end submodule

program main
  use circle_mod
  implicit none

  radius = 1.0
  print *, "area:", area()
end program

Derived data types

In Fortran one can derive structures off of other structures, so called derived data types. The derived types will have the features of the parent type as well as the newly added ones and the general syntax is given by:

type, extends(<parentTypeName>) :: <newTypeName>
  <definitions>
end type <newTypeName>

The following example shows different types of people within a company.

module company_data_mod

  implicit none
  private

  type, public :: phone_type
    integer :: area_code, number
  end type phone_type

  type, public :: address_type
    integer :: number
    character(len=30) :: street, city
    character(len=2) :: state
    integer :: zip_code
  end type address_type

  type, public :: person_type
    character(len=40) :: name
    type(address_type) :: address
    type(phone_type) :: phone
    character(len=100) :: remarks
  end type person_type

  type, public, extends(person_type) :: employee_type
    integer :: phone_extension, mail_stop, id_number
  end type employee_type

  type, public, extends(employee_type) :: salaried_worker_type
    real :: weekly_salary
  end type salaried_worker_type

  type, public, extends(employee_type) :: hourly_worker_type
    real :: hourly_wage, overtime_factor, hours_worked
  end type hourly_worker_type

end module company_data_mod

program main
  use company_data_mod
  implicit none

  type(hourly_worker_type) :: obj

end program main

Destructors

One can define procedures which will be invoked before the object is automatically deleted (out of scope). This is done with the statement final. The following example illustrates it

module person_m
  implicit none

  type :: person_t
    integer, allocatable :: numbers(:)
  contains
    final :: del
  end type person_t
contains
  subroutine del( this )
    type(person_t), intent(inout) :: this
    if (allocated( this%numbers )) deallocate( this%numbers )
  end subroutine del
end module person_m

Abstract base type and deferred procedure

One can set the base type as abstract such that one cannot initialize objects of that type but one can derive sub-types of it (via extends). Specific procedures which should be defined in the sub-type need the property deferred as well as an explicit interface.

The following example illustrates their use.

module shape_m
  implicit none

  type, abstract :: shape_t
    real :: a, b
  contains
    procedure(area_shape_t), deferred :: area
  end type shape_t

  interface
    function area_shape_t( this ) result( A )
      import :: shape_t
      class(shape_t) :: this
      real :: A
    end function area_shape_t
  end interface
end module shape_m

module line_m
  use shape_m
  implicit none
  private

  type, extends(shape_t), public :: line_t
  contains
    procedure :: area
  end type line_t

contains
  function area( this ) result( A )
    class(line_t) :: this
    real :: A

    A = abs( this%a - this%b )
  end function area
end module line_m

module rectangle_m
  use shape_m
  implicit none
  private

  type, extends(shape_t), public :: rectangle_t
  contains
    procedure :: area
  end type rectangle_t

contains
  function area( this ) result( A )
    class(rectangle_t) :: this
    real :: A

    A = this%a * this%b
  end function area
end module rectangle_m

program main
  use line_m
  use rectangle_m

  implicit none

  type(rectangle_t) :: rec
  type(line_t) :: line

  ! line
  line%a = 2.
  line%b = 4.
  print*, "line"
  print*, "-> from:", line%a
  print*, "-> to:", line%b
  print*, "-> length:", line%area()

  ! rec
  rec%a = 3.
  rec%b = 5.
  print*
  print*, "rec"
  print*, "-> side a:", rec%a
  print*, "-> side b:", rec%b
  print*, "-> area:", rec%area()
end program main

Polymorphic Pointer

One can create pointers to child classes by using type definitions in allocate statements and the select type environment. The following example highlights its use.

program main
  use shape_m
  use rectangle_m
  use line_m

  implicit none

  class(shape_t), allocatable :: sh    ! pointer to parent class

  ! allocate( line_t::sh )
  allocate( rectangle_t::sh )          ! allocate using child types

  select type (x => sh)                ! associate block. "x" will be a pointer to the child object
    class is (line_t)                  ! select the right child class (the one we used in the allocate statement)
      x%length = 1.
    class is (rectangle_t)
      x%area = 2.
  end select
end program main

module shape_m
  implicit none

  type, abstract :: shape_t
    ! just an empty class used to implement a parent class.
  end type shape_t
end module shape_m

module line_m
  use shape_m
  implicit none

  type, extends(shape_t) :: line_t
    ! a child class w/ one attribute
    real :: length
  end type line_t
end module line_m

module rectangle_m
  use shape_m
  implicit none

  type, extends(shape_t) :: rectangle_t
    ! a child class w/ another attribute
    real :: area
  end type rectangle_t
end module rectangle_m