Object-oriented Fortran

Classes

Object classes are declared with the 'TYPE' keyword. This declares a class 'object' in the module 'cms_object':

module cms_object
implicit none
    type object
        ! ...
    end type
end module

To create an object of that class use 'TYPE()'

program foo
    use cms_object, only: object
    type(object) :: bar
end program

Member variables

Objects can have their own internal variables

module cms_object
implicit none
    type object
        integer :: foo
        real(kind=8),dimension(:),allocatable :: bar
     end type
end module

Variables are accessed using the '%' operator

program foo
    use cms_object, only: object
    type(object) :: bar

    bar%foo = 5

    allocate(bar%bar(5))
    bar%bar(1) = 4.9
    deallocate(bar%bar)
end program

Destructors

If an object has an 'ALLOCATABLE' variable that variable will need to be freed once you're done with it. This can be done automatically using a destructor, which will be run on the object when it goes out of scope (e.g. at the end of a function)

module cms_object
implicit none
    type object
       integer :: foo
       real(kind=8),dimension(:),allocatable :: bar
    contains
       final :: delete_object
    end type
contains
    subroutine delete_object(this)
        type(object) :: this
        if (allocated(this%bar)) then
            deallocate(this%bar)
        end if
    end subroutine
end module

The destructor can be named anything you wish, although it will be helpful to have a unique name for each object's destructor once we get to inheritance. The destructor is run automatically like

program foo
    use cms_object, only: object
    type(object) :: bar

    bar%foo = 5

    allocate(bar%bar(5))
    bar%bar(1) = 4.9

    ! bar is about to go out of scope at the end of the function
    ! The compiler automatically inserts 'call delete_object(bar)'
end program

Constructors

Constructors are the opposite of destructors, they are run create an object. A constructor is a function or interface with the same name as the object's type

module cms_object
implicit none
    type object
       integer :: foo
       real(kind=8),dimension(:),allocatable :: bar
    contains
       final :: delete_object
    end type

    interface object
       procedure :: constructFromCount
       procedure :: constructFromArray
    end interface
contains
    subroutine delete_object(this)
        ! ...
    end subroutine

    function constructFromCount(count) result(this)
        type(object) :: this
        integer, intent(in) :: count
        allocate(this%bar(count))
    end function
    function constructFromArray(array) result(this)
        type(object) :: this
        real(kind=8), dimension(:), intent(in) :: array
        allocate(this%bar(size(array)))
        this%bar = array
    end function
end module

You call the constructor as if it were a function to initialise the object

program foo
    use cms_object, only: object
    type(object) :: bar

    bar = object(5)
    write(*,*) size(bar%bar)
end program

Now the array will be both created and destroyed automatically.

Object functions

You can add functions to an object by adding to its interface. When the function is called with the '%' operator the object to the left of the % will be passed as the function's first argument (similar to Python)

module cms_object
implicit none
    type object
       integer :: foo
       real(kind=8),dimension(:),allocatable :: bar
    contains
       final :: delete_object
       procedure :: increment
    end type

    interface object
       procedure :: constructFromCount
       procedure :: constructFromArray
    end interface
contains
    ! ...

    subroutine increment(this, value)
        type(object) :: this
        integer :: value

        this%bar = this%bar + 1
    end subroutine
end module

program foo
    use cms_object
    type(object) :: bar

    bar = object(5)

    ! Really runs 'call increment(bar,2)'
    call bar%increment(2)
end program

Assignment operator

If you want to be able to convert between types you can define assignment operators for the class. You will also need to define a custom assignment if the class contains allocatable arrays. These are defined in a module interface

module cms_object
implicit none
    type object
        ! ...
    end type
    ! ...
    interface assignment(=)
        procedure :: assignFromObject
        procedure :: assignFromArray
    end interface
contains
    ! ...
    subroutine assignFromObject(this,other)
        class(object),intent(inout) :: this
        class(object),intent(in) :: other
        allocate(this%bar(size(other%bar)))
        this%foo = other%foo
        this%bar = other%bar
    end subroutine
    subroutine assignFromArray(this,other)
        class(object),intent(inout) :: this
        real(kind=8),dimension(:),intent(in) :: other
        allocate(this%bar(size(other)))
        this%foo = 12
        this%bar = other
    end subroutine
end module
program foo
    use cms_object
    type(object) :: a,b,c
    real(kind=8),dimension(5) array

    a = object(5)
    b = a
    c = array
end program

Other operators

You can also define operators that work on your class, either normal ones like .not., .and. &c or your own custom ones. To do this you add an operator interface to the module

module cms_object
implicit none
    type object
        ! ...
    end type
    ! ...
    interface operator(.eq.)
        procedure :: equalsObject
    end interface
    interface operator(.foo.)
        procedure :: fooObject
    end interface
contains
    ! ...
    function equalsObject(lhs,rhs) return(equal)
        type(object), intent(in) :: lhs,rhs
        logical :: equal
        equal = (lhs%foo .eq. rhs%foo) .and. (lhs%bar .eq. rhs%bar)
    end function
    function fooObject(rhs) return(foo)
        type(object),intent(in) :: rhs
        integer :: foo
        foo = rhs%foo
    end function
end module
program foo
    use cms_object
    type(object) :: a,b
    logical :: equal
    integer :: foo

    equal = a .eq. b
    foo = .foo. b
end program

Operators can either be unary (like .not.) or binary (like .and.). The number of arguments to the function decides which it is.

Full Example

You can find an example of a full object | here. It provides a 'string' class, which handles automatic allocation and deallocation of character strings, as well as some utilities for converting between strings and character arrays.

Some things to note:

  • The module name is prepended with the name of the library it is part of. This helps to avoid name collisions between different libaries
  • The default access level for the module is private, meaning functions cannot be called directly unless that's explicitly permitted. This is handy when there's a lot of interface functions, you can allow calling the interfaces by prohibit calling the actual implementation functions directly, again tidying up the namespace.
  • The member variables of the class are private. This way the implementation details can be changed without having to change external code, for instance if you wanted to make identical strings use the same memory.
  • The length variable is accessible through a member function, however the character data isn't, again so the memory layout could be changed easily. The only way to get the character data is through assigning the string to a character(len=*).
  • The class uses dynamic memory, so contains a destructor and assignment operator
  • Most of the class functions can use strings and character(*) interchangeably through the use of interfaces
  • The class defines a .eq. operator for checking equality, as well as a custom .append. operator to concatenate strings.
  • The functions made available by 'use sawlibf_string' are set to public. Since the 'length' function wasn't declared private in the class that is automatically exported. Also exported are the interfaces, so you can call .append. but not the implementation function appendString.