Modules

Modules

•     modules is the Fortran 90 way of sharing data and code

•     modules are an independent program unit and can contain subprograms

•     enable defining “global” data

•     avoids use of external subprograms and need for interfaces

•     enables data hiding (only required data or subprograms are available to user)

Global Data

•     some data is required by many programs

•     universal constants like pi, e, physical constants are frequently required

•     modules allow these to be declared only once

•     a collection of all known constants declared in a module

•     a program requiring any of these can use only the required constants from this module

•     constant with different precisions may be used

Constant Module

module constants

implicit none

real, parameter :: pi = 3.1415926

real, parameter :: e = 2.7182818

real, parameter :: mass_of_electron = 1.6e-19

real, parameter :: g = 9.8

public :: pi, e, mass_of_electron, g

end module constants

Using Constant Module

program use_constants

use constants

implicit none

•     all declarations in module constants which are public can now be used in the program

•     all constants are available for use in program

•     program and module can be compiled independently using –c option

•     .o files produced can be linked to get code

Use Statement

•     use statement in a program gives the program access to all declarations and subprograms contained in module specified

•     only public entities in the module can be used

•     use statements (can be more than one) appear after program statement before implicit none

•     names used in module cannot be used in program

•     module may be used by another module or a subprogram (no circular use of modules)

 

Renaming and Restriction

•     a program may require only some of the declarations in the module with different names

•     use statement can specify required entities (variables or subprograms) and their names

use constants, only : pi,  grav_const => g

•     only specifies that only constants pi and g from module constants are required

•     g is renamed as grav_const

•     g and other names in module can be used in program for different entities

Sharing Data

•     usually data is shared between program units by passing arguments to subprograms

•     sometimes too many arguments required

•     some variables required by many subprograms

•     reduce number of arguments using “global” variables shared by different subprograms

•     module containing shared variables used by different subprograms

•     variables may be given save attribute, values preserved between different uses of module

Sharing Input Data

•     create a module which contains all input data for a problem and procedure for reading it

•     any program for solving the problem can use this module

•     input data is usually not modified in a program

•     creates a “standard” input format

•     common input file used by all programs

•     many problems have similar types of input

 

Example

module tsp_data

implicit none

integer, parameter :: max_cities = 20

integer, dimension(max_cities,max_cities) :: distance

integer :: no_of_cities

character(len=10) :: filename

public :: get_tsp_data, no_of_cities, distance, max_cities

private :: filename

contains

 

subroutine get_tsp_data(err)

logical, intent(out) :: err

integer :: ios, i, j

print *, "enter name of file"

read *, filename

err = .false.

open(unit=10,file=trim(filename),access="sequential”,&

action="read", form="formatted", status="old",          &

position="rewind", iostat= ios)

if ( ios /= 0) then

print *, "failed to open file"

err = .true.

return

endif

read (unit=10,fmt="(i3)",iostat=ios) no_of_cities

if ( ios /= 0) then

print *, "no_of_cities not given"

err = .true.

return

endif

if (no_of_cities > max_cities) then

print "(a,i6)", "number of cities must be at most",        &

max_cities

err = .true.

return

endif

do i = 1, no_of_cities_

read (unit=10,fmt="(20i4)",iostat=ios) (distance(i,j), &

j = 1, no_of_cities)

if ( ios /= 0) then

print *, "distance not specified correctly"

err = .true.

exit

endif

end do

close(unit=10)

end subroutine get_tsp_data

end module tsp_data

 

Sharing Code

•     modules are more commonly used to share subprograms contained in the module

•     subprograms for related problems are contained in a module to form a “package”

•     any program requiring these uses the module

•     no interfaces required for such subprograms

•     module and program compiled separately

•     module for polynomial operations

Polynomial Module

module polynomial

implicit none

public :: evaluate, add, multiply, read_poly, print_poly

 

contains

function evaluate(a,x) result(value)

real, intent(in) :: x

real, dimension(0:), intent(in) :: a

real :: value

integer :: i, n

n = size(a)-1

value = a(n)

do i = n,1,-1

   value = a(i-1) + x*value

end do

end function evaluate

 

subroutine add(a,b,c)

real, dimension(0:), intent(in) :: a,b

real, dimension(:), allocatable, intent(out) :: c

integer :: n,m

n = size(a)-1

m = size(b)-1

if (allocated(c) ) deallocate(c)

allocate(c(0:max(n,m)))

c = 0

c(0:n) = c(0:n)+a(0:n)

c(0:m) = c(0:m)+b(0:m)

end subroutine  add

 

subroutine multiply(a,b,c)

real, dimension(0:), intent(in) :: a,b

real, dimension(:), allocatable, intent(out) :: c

integer :: i, n, m

n = size(a)-1

m = size(b)-1

if (allocated(c)) deallocate(c)

allocate(c(0:n+m))

c = 0

do i = 0,m

c(i:i+n) = c(i:i+n) + b(i)*a(0:n)

end do

end subroutine multiply

 

subroutine read_poly(a)

real,dimension(:),intent(out), allocatable :: a

integer :: deg

print *, "enter degree of polynomial"

read *, deg

if (allocated(a)) deallocate(a)

allocate(a(0:deg))

print *, "enter coefficients starting with constant"

read *, a(0:)

end subroutine read_poly

 

subroutine print_poly(a)

real,dimension(0:),intent(in) :: a

print *, "polynomial coefficients starting with constant"

print "(10f6.2)", a(0:size(a)-1)

end subroutine print_poly

end module polynomial

•     this approach works only in Fortran 95

•     dummy argument cannot be allocatable in Fortran 90

•     array of required size created before calling subprogram