What is object-oriented programming?
Object-Oriented Programming (OOP) describes an approach to programming where a program is
viewed as a collection of interacting, but mostly independent software components.
These software components are known as objects and they are typically implemented
in a programming language as an entity that encapsulates both data and procedures.
A very simple one page course is available here.
It explains from a simple example the following concepts:
- Abstraction
- Encapsulation
- Hierarchy and Inheritance
- Typing
- Genericity
For this lesson, we start from our pgmImage derived type and explain how to change it to a Fortran 2003 Object-oriented data
structure (class). Then on this example we explain what we mean by abstraction, encapsulation, hierarchy and
inheritance.
Abstraction
If we go back to one of our first lesson, we defined a pgmImage as being a simple 2D array. Then we wrote two subroutines to read a pgmImage
because we have pgm images written and stored as ASCII files (text files) and pgm images written and stored as binary files.
One significant commonality between PGMA and PGMB is that images are both PGM images and the "only" difference is when the image is read or written.
Other processing on the image is identical. This is what we call abstraction: finding the significant commonalities and ignore trivial differences.
Encapsulation
What we have seen with derived types is closed to OOP in the sense that variables of a derived-type were all grouped together inside the created derived type
(as they belong to the same entity):
TYPE pgmImage
CHARACTER(LEN=2) :: magics
CHARACTER(LEN=255) :: createdby
INTEGER :: nx
INTEGER :: ny
INTEGER, POINTER :: A(:, :)
END TYPE pgmImage
All the subroutines and functions we could use for this new derived-type were included in our module pgm_library
MODULE pgm_library
IMPLICIT NONE
TYPE pgmImage
CHARACTER(LEN=2) :: magics
CHARACTER(LEN=255) :: createdby
INTEGER :: nx
INTEGER :: ny
INTEGER, POINTER :: A(:, :) ! I could use ALLOCATABLE too
! It is Fortran 95 and not Fortran 90
END TYPE pgmImage
CONTAINS
SUBROUTINE read_pgm(filename,img)
IMPLICIT NONE
character(LEN=*), intent(IN) :: filename ! intent is IN because filename
! is not modified in the subroutine
TYPE(pgmImage), intent(out) :: img
END SUBROUTINE read_pgm
.
.
.
END MODULE pgm_library
However, these subroutines/functions are not part of the derived-type itself and the advantage of writing them in the same
module (with the derived-type) is for readability. With an Object-oriented approach, we will give more information to users (programmers using your
new derived-type), telling them which subroutines/functions can be applied (i.e. making sense) to this new derived-type:
MODULE pgm_library
IMPLICIT NONE
TYPE pgmImage
CHARACTER(LEN=2) :: magics
CHARACTER(LEN=255) :: createdby
INTEGER :: nx
INTEGER :: ny
INTEGER, POINTER :: A(:, :) ! I could use ALLOCATABLE too
! It is Fortran 95 and not Fortran 90
CONTAINS ! this contains is used to list the subroutines/functions attached to this data type
PROCEDURE :: read => read_pgm ! needs to have an "official" name (read) and an alias (read_pgm)
PROCEDURE :: free => free_pgm
END TYPE pgmImage
CONTAINS
SUBROUTINE read_pgm(filename,img)
IMPLICIT NONE
character(LEN=*), intent(IN) :: filename ! intent is IN because filename
! is not modified in the subroutine
CLASS(pgmImage), intent(inout) :: img ! we need to use CLASS instead of TYPE and CANNOT have INTENT(OUT)
END SUBROUTINE read_pgm
.
.
.
END MODULE pgm_library
And the main program would be:
program matrix_main
USE pgm_library
implicit none
! create a new object image of type pgmImage
type(pgmImage) :: image
call image%read("../../data/moon.pgm") ! call read and not read_pgm
! I do not need to pass image as an argument as
! read is "belong" to image and is applied to "itself"
call image%free() ! free is called to deallocate dynamic arrays, etc.
end program matrix_main
Hierarchy and inheritance
The CLASS keyword allows F2003 programmers to create polymorphic variables.
Polymorphism is a term used in software development to describe a variety of
techniques employed by programmers to create
flexible and reusable software components.
In programming languages, a polymorphic object is an entity, such as a variable or a procedure,
that can hold or operate on values of differing types during the program's execution. Because a polymorphic object can operate on a variety of values and types, it can also be used in a variety of programs, sometimes with little or no change by the programmer. The idea of write once, run many, also known as code reusability, is an important characteristic to the programming paradigm known as Object-Oriented Programming (OOP).
A polymorphic variable is a variable whose data type is dynamic at runtime.
It must be a pointer variable, allocatable variable, or a dummy argument.
Below are some examples of polymorphic variables:
subroutine init(image)
class(pgmImage) :: image ! polymorphic dummy argument
class(pgmImage), pointer :: p ! polymorphic pointer variable
class(pgmImage), allocatable:: als ! polymorphic allocatable variable
end subroutine
In the example above, the image, p, and als polymorphic variables can each hold values of type pgmImage or any type extension of pgmImage.
The image dummy argument receives its type and value from the actual argument image of subroutine init().
The polymorphic pointer variable p above can point to an object of type pgmImage or any of its extensions.
For example,
!//
!///////////////////////////////////////////////////////////////////////////////
MODULE matrix_mod
IMPLICIT NONE
!// Make everything not specified as public invisible from outside the
!// module
PRIVATE
!// Declare a type called matrix
TYPE, PUBLIC :: matrix
!// Internal variables for this type
INTEGER :: nx = 0
INTEGER :: ny = 0
INTEGER, POINTER :: A(:, :) => null()
CONTAINS
!// the procedures to load data, to write data to the screen,
!// to clear the contents of an object and to copy data from one object
!// to another
PROCEDURE :: load => load_data
PROCEDURE :: dump => dump_data
PROCEDURE :: clear => clear_data
PROCEDURE :: copy => copy_data
END TYPE matrix
!// A child object based on the parent object maps containing a 2D matrix
!// of integer values to hold an pgmImage map
TYPE, PUBLIC, EXTENDS(matrix) :: pgmImage
character(len=2) :: magics = 'P2'
character(len=255) :: createdby = 'NONE'
integer :: maxgray = 0
END TYPE pgmImage
CONTAINS
!// A common subroutine for all the object types to load data from a file into the object
SUBROUTINE load_data(this, filename)
!// A polymorphic object
CLASS(matrix) :: this
character(len=255), intent(in) :: filename
!// Index and status variable
INTEGER :: i, res
!// Find out what kind of object this is
SELECT TYPE(this)
!// Is it a pgmImage object
CLASS IS (pgmImage)
!// Yes, call the corresponding procedure
CALL load_pgmImage(this, filename)
CLASS DEFAULT
call load_matrix(this, filename)
END SELECT
END SUBROUTINE load_data
SUBROUTINE load_matrix(this, filename)
!// A polymorphic object
CLASS(matrix) :: this
character(len=255), intent(in) :: filename
!// File unit number
INTEGER :: lun=10
OPEN(UNIT=lun, file= filename)
read(lun,*) this%nx, this%ny
allocate(this%A(this%nx, this%ny))
read(lun,*) this%A
CLOSE(UNIT=lun)
END SUBROUTINE load_matrix
SUBROUTINE load_pgmImage(this, filename)
!// A polymorphic object
CLASS(pgmImage) :: this
character(len=255), intent(in) :: filename
!// File unit number
INTEGER :: lun=10
OPEN(UNIT=lun, file= filename)
read(lun,*) this%magics
read(lun,*) this%createdby
read(lun,*) this%nx, this%ny
read(lun,*) this%maxgray
allocate(this%A(this%nx, this%ny))
read(lun,*) this%A
CLOSE(UNIT=lun)
END SUBROUTINE load_pgmImage
SUBROUTINE dump_data(this)
!// A polymorphic object
CLASS(matrix) :: this
!// Find out what kind of object this is
SELECT TYPE(this)
!// Is it an pgmImage object
CLASS IS (pgmImage)
!// Yes, write the header and integer values from the array to the screen
write(*,'(a2)') this%magics
write(*,'("# Created by dump_data")')
write(*,*) this%nx, this%ny
write(*,*) this%maxgray
write(*,*) this%A
CLASS DEFAULT
!// Yes, write the header and integer values from the array to the screen
write(*,*) this%nx, this%ny
write(*,*) this%A
END SELECT
END SUBROUTINE dump_data
SUBROUTINE clear_data(this)
!// A polymorphic object
CLASS(matrix) :: this
!// Clear the header variables
this%nx = 0
this%ny = 0
DEALLOCATE(this%A)
!nothing specific here...
END SUBROUTINE clear_data
FUNCTION copy_data(this) RESULT(that)
CLASS(matrix) :: this
CLASS(*), POINTER :: that
CLASS(pgmImage), POINTER :: eptr
SELECT TYPE(this)
CLASS IS (pgmImage)
ALLOCATE(eptr)
eptr%magics = this%magics
eptr%createdby = this%createdby
eptr%maxgray = this%maxgray
eptr%nx = this%nx
eptr%ny = this%ny
ALLOCATE(eptr%A(eptr%nx,eptr%ny))
eptr%A(:,:) = this%A(:,:)
that => eptr
CLASS DEFAULT
eptr%nx = this%nx
eptr%ny = this%ny
ALLOCATE(eptr%A(eptr%nx,eptr%ny))
eptr%A(:,:) = this%A(:,:)
that => eptr
END SELECT
END FUNCTION copy_data
END MODULE matrix_mod
And the main program could be:
program matrix_main
use matrix_mod
implicit none
! create one new object image
type(matrix),pointer :: m
type(pgmImage),pointer :: image
!// Holding the number of command line arguments
INTEGER :: argc
character(len=255) :: filename
character(len=255) :: typeOfImage
argc = COMMAND_ARGUMENT_COUNT()
if (argc == 2) THEN
call get_command_argument(1,filename)
call get_command_argument(2,typeOfImage)
SELECT CASE(typeOfImage)
CASE('PGM')
allocate(image)
image = pgmImage()
call image%load(filename)
call image%dump()
deallocate(image)
CASE('MATRIX')
allocate(m)
m = matrix()
call m%load(filename)
call m%dump()
deallocate(m)
END SELECT
else
write(*,*) 'A filename is needed!'
endif
end program matrix_main