Fortran/OOP in Fortran
Object-oriented programming
editModule
editOverview
editData can be gathered in module
s. The general form is given by
module <name>
[use <module_names>]
[<declarations>]
contains
[<subroutines and functions>]
end module [<name>]
Data access
editThere 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
editOne can include the module's public data in outside code. There are three ways.
use <moduleName>
: includes all public data and methodsuse <moduleName>, <renames>
: includes all public data and methods, but renames some public data or methodsuse <moduleName>, only: <subset>
: includes only some public data and methods
Example
editGeneral overview
editmodule test_m
implicit none
private ! All data is by default private.
! These procedures are set public -> accessible outside
public print_coords, set_coords
real :: x, y ! Not accessible outside module.
contains
subroutine print_coords
print *, "x, y", x, y
end subroutine
subroutine set_coords(new_x, new_y)
real, intent(in) :: new_x, new_y
x = new_x
y = new_y
end subroutine
end module
program main
use test_m ! Import the "test_m" module
implicit none
call set_coords(1.0, 1.0) ! Call the public procedure from test_mod
call print_coords
end program
Data access
editmodule data_access_m
implicit none
private
public a, b
protected b
private c
integer :: a = 1
integer :: b = 1
integer :: c = 1
end module
program main
use data_access_m
! 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
Using modules
editmodule 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
editModules 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
editSplitting of definitions and implementations
edit!> 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
editIn 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
The following example shows different types of people within a company.
module company_data_mod
implicit none
private
public phone_type, address_type, person_type, employee_type, salaried_worker_type, hourly_worker_type
type phone_type
integer :: area_code, number
end type
type address_type
integer :: number
character (len=:), allocatable :: street, city
character (len=2) :: state
integer :: zip_code
end type
type person_type
character (len=:), allocatable :: name
type (address_type) :: address
type (phone_type) :: phone
character (len=:), allocatable :: remarks
end type
type, extends (person_type) :: employee_type
integer :: phone_extension, mail_stop, id_number
end type
type, extends (employee_type) :: salaried_worker_type
real :: weekly_salary
end type
type, extends (employee_type) :: hourly_worker_type
real :: hourly_wage, overtime_factor, hours_worked
end type
end module
program main
use company_data_mod
implicit none
type (hourly_worker_type) :: obj
end program
Destructors
editOne 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
integer, allocatable :: numbers(:)
contains
final :: del
end type
contains
subroutine del(this)
!! example for a derived type's destructor. allocatables are
!! deallocated automatically anyways. this is just to show the usage of
!! "final".
type (person), intent (inout) :: this
if (allocated(this%numbers)) deallocate (this%numbers)
end subroutine
end module
Abstract base type and deferred procedure
editOne 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
real :: a, b
contains
procedure :: print => shape_print
procedure (area_shape), deferred :: area
end type
interface
real function area_shape(this)
import :: shape
class (shape), intent (in) :: this
end function
end interface
contains
subroutine shape_print(this)
class (shape), intent (in) :: this
print *, 'a,b', this%a, this%b
end subroutine
end module
module line_m
use shape_m
implicit none
private
public line
type, extends (shape) :: line
contains
procedure :: area
end type
contains
real function area(this)
class (line), intent (in) :: this
area = abs(this%a - this%b)
end function
end module
module rectangle_m
use shape_m
implicit none
private
public rectangle
type, extends(shape) :: rectangle
contains
procedure :: area
end type
contains
real function area(this)
class (rectangle), intent (in) :: this
area = this%a * this%b
end function
end module
program main
use line_m
use rectangle_m
implicit none
type (line) :: l
type (rectangle) :: r
! line
l%a = 2.0
l%b = 4.0
print *, "line ... "
call l%print
print *, "-> from: ", l%a
print *, "-> to: ", l%b
print *, "-> length:", l%area()
! rectangle
r%a = 3.0
r%b = 5.0
print *
print *, "rectangle ..."
call r%print
print *, "-> side a:", r%a
print *, "-> side b:", r%b
print *, "-> area: ", r%area()
end program
Polymorphic Pointer
editOne can create pointers to child classes by using type definitions in allocate
statements and the select type
environment.
The following example highlights its use.
module shape_m
implicit none
type, abstract :: shape
! Just an empty class used to implement a parent class.
! reason for abstract: there shouldnt be objects of TYPE(!) shape, just
! polymorphic CLASS instances.
end type
end module
module line_m
use shape_m
implicit none
type, extends (shape) :: line
! A child class w/ one attribute.
! Reason for extends(shape): polymorphic shape pointer can point to
! objects of this type.
real :: length
end type
end module
module rectangle_m
use shape_m
implicit none
type, extends (shape) :: rectangle
! A child class w/ another attribute
! Reason for extends(shape): (see explanation in line type)
real :: area
end type
end module
program main
use rectangle_m
use line_m
implicit none
class (shape), allocatable :: sh ! Pointer to parent class.
! allocate (line :: sh)
allocate (rectangle :: sh) ! Allocate using child types
select type (x => sh) ! Associate block. "x" will be a pointer to the child object and of its type(!!)
type is (line) ! Select the right child type (the one we used in the allocate statement)
x%length = 1.0
print *, 'line length', x%length
type is (rectangle)
x%area = 2.0
print *, 'rectangle area', x%area
! class is () ! Select by using classes.
class default ! If nothing of the above applied.
error stop 'class/type not specified!'
end select
end program