Modules and Derived Types

Generic Procedures

•     modules provide convenient way of manipulating user defined types

•     allow defining “generic” subprograms

•     a generic subprogram is a common name given to a collection of subprograms

•     subprograms with common generic name must differ in number, type or rank of arguments

•     subprograms performing same task on variables of different types are given same generic name

Swap Routines

•     separate subroutine has to be written for swapping variables of different types

•     subroutine for swapping reals cannot be used for swapping integers or derived type variables

•     write a generic swap routine which will call the appropriate type specific routine depending on type of actual argument

•     user needs to know only the generic name

•     specific routines contained in a module and are private to the module

Module for Swapping

module swap_routines

use type_def

! type_def is a module containing all type definitions

implicit none

private  ! type_def module is not available for use

interface swap   ! swap is a generic name

module procedure swap_int  ! specific subroutines

module procedure swap_real

module procedure swap_point

module procedure swap_circle

end interface ! name should not be put here

public :: swap

private :: swap_int, swap_real, swap_point, swap_circle

contains

 

subroutine swap_int(i,j)

integer, intent(inout) :: i,j

integer :: temp

temp = i

i = j

j = temp

end subroutine swap_int

 

 

subroutine swap_point(p,q)

type(point), intent(inout) :: p, q

type(point) :: temp

temp = p

p = q

q = temp

end subroutine swap_point

! put subroutines for swapping all types of variables here

……….

end module swap_routines

 

Using Generic Procedures

•     any program using module swap_routines and type_def can call swap with arguments of any type defined in module type_def (or intrinsic type)

•     actual subroutine to be used determined from type of arguments (should be unique)

•     subprograms with same generic name must be all subroutines or all  functions

•     intrinsic function names may also be used

•     sqrt maybe defined for integer arguments

•     functions like abs are already generic

Operator Overloading

•     unlike intrinsic types, there are no operators defined for derived types

•     use modules to define our own operators

•     extend the meaning of intrinsic operators like +, *, = (assignment) to other types

•     module containing definition of a type and operations on that type can be created

•     user can only use the defined operations on type

•     internal details hidden from user

•     makes programs more simpler and readable

Rational Arithmetic

•     define a new type called rational numbers

•     extend all arithmetic and relational operators to rational numbers (also for arrays)

•     “package” everything in a module hiding internal details

•     user can use the module as a black box which performs rational arithmetic

•     more accurate results can be obtained

Rational Module

module rational_arith

! this module implements rational arithmetic

implicit none

type ::  rational

private

! components of type rational cannot be used

integer :: num, denom

end type rational

interface operator(+)

module procedure rat_add

end interface ! operator + defined by rat_add

 

interface operator(-)

module procedure rat_subtract

end interface

interface operator(*)

module procedure rat_mult

end interface

interface operator(/)

module procedure rat_divide

end interface

interface operator(.inverse.) ! new operator

module  procedure invert

end interface

 

interface operator(.upon.)

module procedure rat_create

end interface

interface assignment(=)

module procedure int_assign

module procedure real_assign

end interface

! for an operator, procedure should be a function with one or

! two intent(in) arguments, for assignment, it should be a

! subroutine with first argument intent(out) (LHS) and second

! argument intent(in) (RHS of assignment)

public :: rational, print_rat, read_rat, operator(+), operator(-)

public :: operator(*), operator(/), operator(.inverse.)

public :: operator(.upon.), assignment(=)

private :: rat_add, rat_subtract, rat_mult, rat_divide, rat_create

private :: invert, reduce, gcd, int_assign, real_assign

contains

! operators with extended definition made public

! actual functions for these are private

! users of module can only use these operators

! internal representation of rational numbers is private

function rat_add(r_1,r_2) result(r_3)

type(rational), intent(in) :: r_1, r_2

type(rational) :: r_3

r_3%num =  r_1%num * r_2%denom +                   &

                   r_1%denom * r_2%num

r_3%denom = r_1%denom * r_2%denom

r_3 = reduce(r_3)

end function rat_add

 

function rat_subtract(r_1,r_2) result(r_3)

type(rational), intent(in) :: r_1, r_2

type(rational) :: r_3, r_4

r_4%num = - r_2%num

r_4%denom = r_2%denom

r_3 = r_1 + r_4

end function rat_subtract

 

function rat_mult(r_1,r_2) result(r_3)

type(rational), intent(in) :: r_1, r_2

type(rational) :: r_3, r_4

r_4%num = r_1%num

r_4%denom = r_2%denom

r_3 = reduce(r_4)

r_4%num = r_2%num

r_4%denom = r_1%denom

r_4 = reduce(r_4)

r_3%num = r_3%num * r_4%num

r_3%denom = r_3%denom * r_4%denom

end function rat_mult

 

function rat_divide(r_1,r_2) result(r_3)

type(rational), intent(in) :: r_1, r_2

type(rational) :: r_3

r_3 = .inverse. r_2

r_3 = r_1 * r_3

end function rat_divide

function invert(r_1) result(r_2)

type(rational), intent(in) :: r_1

type(rational) :: r_2

r_2%num = r_1%denom

r_2%denom = r_1%num

end function invert

 

function gcd(n,m) result(g)

integer, intent(in) :: n, m

integer :: a, b, g, temp

a = n

b = m

do

if ( b == 0) exit

temp = modulo(a,b)

a = b; b = temp

end do

g = a

end function gcd

 

function reduce(r_1) result(r_2)

type(rational), intent(in) :: r_1

type(rational) :: r_2

integer :: g

g = gcd(r_1%num, r_1%denom)

r_2%num = r_1%num/g

r_2%denom = r_1%denom/g

end function reduce

 

subroutine read_rat(r_1)

type(rational), intent(out) :: r_1

print *, "enter number, numerator first"

read *, r_1%num, r_1%denom

if ( r_1%denom < 0) then

     r_1%num = - r_1%num

     r_1%denom = - r_1%denom

endif

r_1 = reduce(r_1)

end subroutine read_rat

! use separate module for input/output of all types

 

subroutine print_rat(r_1)

type(rational), intent(in) :: r_1

print "(i8, /, a8, /, i8)", r_1%num, "--------",            &

         r_1%denom

end subroutine print_rat

 

function rat_create(i,j) result(r)

integer, intent(in) :: i, j

type(rational) :: r

r%num = i

r%denom = j

if ( r%denom < 0) then

r%num = - r%num

r%denom = - r%denom

end if

r = reduce(r)

end function rat_create

 

subroutine int_assign(i, r_1)

type(rational), intent(in) :: r_1

integer, intent(out) :: i

i = r_1%num/r_1%denom

end subroutine int_assign

 

subroutine real_assign(x,r_1)

type(rational), intent(in) :: r_1

real, intent(out) :: x

x = real(r_1%num)/real(r_1%denom)

end subroutine real_assign

end module rational_arith

 

Using Rational Arithmetic

program use_rat

! this program finds rational solutions to system of linear

! equations with rational coefficients

use rational_arith

implicit none

integer, parameter :: max_var=10

type(rational), dimension(max_var,max_var+1) :: a

type(rational), dimension(max_var) :: x

type(rational) :: r

integer :: i, j, k, n

 

print *, "type number of variables, at most    ", max_var

read *, n

do i = 1,n

print *, "enter coefficients of equation   ", i

do j = 1, n+1

call read_rat(a(i,j))

end do

end do

 

 

do i = 1, n

r = a(i,i)

do j = i, n+1

a(i,j) = a(i,j)/r

end do

do j = i+1, n

r = a(j,i)

do k = i,n+1

a(j,k) = a(j,k)-a(i,k)*r

end do

end do

end do

 

 

do i = n, 1, -1

x(i) = a(i,n+1)

do j = i+1, n

x(i) = x(i) - a(i,j)*x(j)

end do

end do

do i = 1,n

print *, "value of variable  ", i , "   is"

call print_rat(x(i))

end do

end program use_rat

 

Comments

•     extend module to include comparison operations

•     include array operations as well

•     use a “big integer” module for more accuracy

•     changing type of num, denom does not affect user’s program

•     similar modules available for large precision reals

•     once developed can be used for any program