A module exists to make some or all of the entities declared within it accessible to more than one program unit. A subprogram which is contained within a module is called a module procedure. A subprogram which is placed inside a module procedure, an external procedure, or a main program is called an internal procedure.
The following diagram illustrates the nesting of subprograms in program units:
The form of the program units and procedures is summarised below.
[PROGRAM program_name]
[specification-statements]
[executable-statements]
[CONTAINS
internal procedures]
END [PROGRAM [program_name]]
Module:
MODULE module_name
[specification-statements]
[executable-statements]
[CONTAINS
module procedures]
END [MODULE [module_name]]
[RECURSIVE] SUBROUITNE subroutine_name(dummy-argument-list)
[specification-statements]
[executable-statements]
[CONTAINS
internal procedures]
END [SUBROUTINE [subroutine-name]]
or
[type] [RECURSIVE] FUNCTION function_name &
(dummy-argument-list) [RESULT(result_name)]
[specification-statements]
[executable-statements]
[CONTAINS
internal procedures]
END [FUNCTION [function-name]]
Module procedures have exactly the same form as external procedures except that the word SUBROUTINE or FUNCTION must be present on the END statement.
Internal procedures also must have the word SUBROUTINE or FUNCTION present on the END statement:
[RECURSIVE] SUBROUTINE subroutine_name(dummy-argument-list)
[specification-statements]
[executable-statements]
END SUBROUTINE [subroutine_name]
[type] [RECURSIVE] FUNCTION function_name &
(dummy-argument-list) [RESULT (result_name)]
[specification-statements]
[executable-statements]
END FUNCTION [function_name]
Fortran 77 contained only external procedures, whereas in Fortran 90, structurally, procedures may be:
The internal procedures are collected together at the end of the program unit and are preceded by a CONTAINS statement. For example,
PROGRAM main
IMPLICIT NONE
REAL :: a,b,c
.
.
.
mainsum=add()
.
.
.
CONTAINS
FUNCTION add()
IMPLICIT NONE
REAL :: add !a,b,c,defined in `main'
add=a+b+c
END FUNCTION add
END PROGRAM main
Variables defined in the program unit, remain defined in the internal procedure, unless redefined there. It is good practice to declare all variables used in subprograms in order to avoid the use of global variables in the wrong context.
SUBROUTINE arithmetic(n,x,y,z)
IMPLICIT NONE
INTEGER :: n
REAL,DIMENSION(100) :: x,y,z
.
.
.
CONTAINS
FUNCTION add(a,b,c) RESULT(sum)
IMPLICIT NONE
REAL,INTENT(IN) :: a,b,c
REAL :: sum
sum = a + b + c
END FUNCTION add
END SUBROUTINE arithmetic
However, when the compiler calls an external subprogram, this information is not available and is said to be implicit. The Fortran 90 interface block provides a means of making this information available. The general form of the interface block is:
INTERFACE
interface body
END INTERFACE
The interface body consists of the FUNCTION (or SUBROUTINE) statement, argument type declaration statements, and the END FUNCTION (or END SUBROUTINE) statement. In other words it is an exact copy of the subprogram without its executable statements or internal subprograms. For example,
INTERFACE
FUNCTION func(x)
REAL,INTENT(IN) :: x !INTENT is described in the next section
END FUNCTION func
END INTERFACE
The interface block must be placed in the calling program unit. Note that an interface block can contain interfaces to more than one procedure.
INTEGER, INTENT(IN) :: x
REAL,INTENT(OUT) :: y
REAL, INTENT(INOUT) :: Z
If the intent is IN, the argument value may not be changed within the subprogram. If the intent is OUT, the argument may only be used to return information from the procedure to the calling program. If the intent is INOUT, then the argument may be used to transfer information in both directions between the procedure and calling program.
An Example
SUBROUTINE swapreal(a,b)
IMPLICIT NONE
REAL,INTENT(INOUT) :: a,b
REAL :: temp
temp = a
a = b
b = temp
END SUBROUTINE swapreal
This is used by:
CALL swapreal(x,y)
READ(UNIT=5,FMT=101,END=9000) X,Y,Z
When a procedure has several arguments, keywords are an excellent way of avoiding confusion between arguments. The advantage of using keywords is that you don't need to remember the order of the parameters, but you do need to know the variable names used in the procedure.
For example, we could have the following internal function:
REAL FUNCTION area(start,finish,tol)
IMPLICIT NONE
REAL, INTENT(IN) :: start,finish,tol
.
.
.
END FUNCTION area
which could be called by:
a=area(0.0,100.0,0.00001)
b=area(start=0.0,tol=0.00001,finish=100.0)
c=area(0.0,tol=0.00001,finish=100.0)
where a, b and c are variables declared as REAL. All arguments prior to the first keyword must match -- once a keyword is used all the rest must use keywords. Hence it is not possible to say:
c=area(0.0,tol=0.00001,100.0) !not allowed
Note that an interface is not required in the above example, and similarly one would not be required for a module subprogram with keyword arguments. This is because both have explicit interfaces. In the case of an external procedure with argument procedures, an interface must be provided.
REAL FUNCTION area(start,finish,tol)
IMPLICIT NONE
REAL,INTENT(IN),OPTIONAL :: start, finish, tol
.
.
.
END FUNCTION area
This could be called by:
a=area(0.0,100.0,0.010)
b=area(start=0.0,finish=100.0,tol=0.01)
c=area(0.0)
d=area(0.0,tol=0.01)
where a, b, c and d are variables declared as REAL. The intrinsic logical function PRESENT is used to check for the presence of an optional argument. For example, in the function example above it may be necessary to both check for the presence of the variable tol, and set a default if tol is absent. This is achieved as follows:
REAL :: ttol
IF (PRESENT(tol)) THEN
ttol = tol
ELSE
ttol = 0.01
END IF
The local variable ttol is used here as this may be redefined, whereas the argument tol cannot be changed (as it is INTENT(IN))
As in the case of keyword arguments, if the procedure is external and has any optional arguments, an interface must be supplied. Thus, if the function in the example above was external, the following interface block would need to be provided:
INTERFACE
REAL FUNCTION area(start,finish,tol)
REAL,INTENT(IN),OPTIONAL :: start, finish, tol
END FUNCTION area
END INTERFACE
If the argument procedure is an external procedure, you are recommended to supply an interface block in the calling program unit. For example, consider the external function func:
REAL FUNCTION func(x,y)
IMPLICIT NONE
REAL,INTENT(IN) :: x,y
...
END FUNCTION func
Suppose the subroutine area passes func as an argument, then the calling program unit would contain
...
INTERFACE
REAL FUNCTION func(x,y)
REAL,INTENT(IN) :: x,y
END FUNCTION func
END INTERFACE
...
CALL area(func,start,finish,tol)
FUNCTION add(a,b,c) RESULT(sum)
IMPLICIT NONE
REAL,INTENT(IN) :: a,b,c
REAL :: sum
sum = a + b + c
END FUNCTION add
Directly recursive functions, Here!, must have a RESULT variable.
FUNCTION add_vec (a,b,n)
IMPLICIT NONE
REAL, DIMENSION (n) :: add_vec
INTEGER, INTENT(IN) :: n
REAL, DIMENSION (n), INTENT(IN) :: a, b
DO i=1,n
add_vec(i) = a(i) + b(i)
END DO
END FUNCTION add_vec
Note that if the array-valued function is external, an interface must be provided in the calling program.
INTERFACE
FUNCTION add_vec (a,b,n)
REAL, DIMENSION (n) :: add_vec
INTEGER, INTENT(IN) :: n
REAL, DIMENSION (n), INTENT(IN) :: a, b
END FUNCTION add_vec
END INTERFACE
The classic textbook example of a recursive function, is the factorial calculation:
RECURSIVE FUNCTION fact(n) RESULT (res)
IMPLICIT NONE
INTEGER INTENT(IN) :: n
INTEGER :: res
IF (n.eq.1) THEN
res=1
ELSE
res=n*fact(n-1)
ENDIF
END FUNCTION fact
An important application of recursive procedures is where we have a variable number of DO loops:
DO
DO
DO
.
.
.
END DO
END DO
END DO
For example, suppose we want to write a program called ANOVA to analyse a general factorial design. At the time of writing the program we don't know how many factors there are. Even Fortran 90 doesn't allow us to declare arrays with a variable number of dimensions, and so it is usual for this problem to use a one-dimensional array and calculate the offset in the program. To calculate this offset we still seem to need a number of DO loops equal to the number of factors in the model.
Consider the sub-problem of reading in the initial data. (For reasons specific to the problem, the array needs to be of length
where each factor will be represented at a specific number of levels.)
Fortran 90 allows us to code this as follows:
SUBROUTINE anova(factors,level,x, ... )
INTEGER,INTENT(IN) :: factors
INTEGER,DIMENSION(:),INTENT(IN) :: level
REAL,DIMENSION(:),INTENT(OUT) :: x
.
.
.
INTEGER :: i,k,n,element
INTEGER,DIMENSION(factors) :: c,istep
n = factors + 1
DO i=1,factors
IF (i .EQ. 1) THEN
istep(i) = 1
ELSE
istep(i) = istep(i-1) * (level(i-1) + 1)
END IF
END DO
CALL data
.
.
.
CONTAINS
RECURSIVE SUBROUTINE data
INTEGER :: cn
n = n-1
IF (n .EQ. 0) THEN
element = 1
DO k=1,factors
element = element + (c(factors + 1 - k) - 1) * istep(k)
read *,x(element)
END DO
ELSE
DO cn=1,level(factors+1-n)
c(n) = cn ! do-variable must be a simple variable
CALL data
END DO
END IF
n = n + 1
END SUBROUTINE data
END SUBROUTINE anova
INTERFACE generic_name
specific_interface_body
specific_interface_body
.
.
.
END INTERFACE
All the procedures specified in a generic interface block must be unambigously differentiated, and as a consequence of this either all must be subroutines or all must be functions.
For example, suppose we want a subroutine to swap two numbers whether they are both real or both integer. This would require two external subroutines:
SUBROUTINE swapreal
IMPLICIT NONE
REAL, INTENT(INOUT) :: a,b
REAL :: temp
temp=a
a=b
b=temp
END SUBROUTINE swapreal
SUBROUTINE swapint
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: a,b
temp=a
a=b
b=temp
END SUBROUTINE swapint
This could be invoked with CALL swap(x,y), provided there is an interface block:
INTERFACE swap
SUBROUTINE swapreal (a,b)
REAL, INTENT(INOUT) :: a,b
END SUBROUTINE swapreal
SUBROUTINE swapint (a,b)
INTEGER, INTENT(INOUT) :: a,b
END SUBROUTINE swapint
END INTERFACE
The module is important for both sharing data and sharing procedures (known as module procedures) between program units. Modules also provide a means of global access to entities such as derived type definitions and associated operators. A program may include several different modules, but they must all have a different names.
The form of a module is:
MODULE module-name
[specification-statements]
[executable-statements]
[CONTAINS
module-procedures]
END [MODULE [module-name]]
MODULE globals
REAL, SAVE :: a,b,c
INTEGER, SAVE :: i,j,k
END MODULE globals
Note the use of the SAVE attribute. This allows modules to be used to provide global data. This simple use of the module is a substitute for the COMMON block used previously in Fortran 77.
The data is made accessible in other program units by supplying the USE statement, i.e.
USE globals
The USE statement is non-executable, and must appear at the very beginning of a program unit before any other non-executables, and after the PROGRAM, or other program unit statement. A program unit may invoke a number of different modules by having a series of USE statements. Note that a module itself may `USE' another module, but a module cannot invoke itself either directly or indirectly.
The use of variables from a module could potentially cause problems if the same names have been used for different variables in different parts of a program. The USE statement can overcome this problem by allowing the specification of a different local name for data accessed from a module. For example,
USE globals, r=>a, s=>b
Here, r and s are used to refer to the module data items a and b, and so a and b can be used for something completely different within the program unit. The => symbols link the local name with the module name.
There is also a form of the USE statement which limits access to certain items within the module. This requires the qualifier ONLY followed by a colon and an only-list. For example, only variables a and c can be accessed via the statement:
USE globals, ONLY : a,c
These two facilities can also be combined:
USE globals, ONLY : r=>a
A program unit may have more than one USE statement referring to the same module. However, note that a USE statement with ONLY does not cancel out a less restrictive USE statement.
Module procedures are invoked using the normal CALL statement or function reference, but can only be invoked by a program unit which has invoked, via the USE statement, the module which contains the procedures.
A module procedure may call other module procedures in the same module. The data declared in the module before the CONTAINS statement is directly accessible to all the module procedures. However, any items declared within a module procedure are local and cannot be accessed outside that procedure.
Module procedures can be useful for several reasons. For example, a module which defines the structure of a particular set of data could also include special procedures needed to operate on the data, or a module could be used to hold a library of related procedures.
For example. a module can be used to `add' variables with derived type:
MODULE point_module
TYPE point
REAL :: x,y
END TYPE point
CONTAINS
FUNCTION addpoints(p,q)
TYPE (point),INTENT(IN) :: p,q
TYPE (point) :: addpoints
addpoints%x = p%x + q%x
addpoints%y = p%y + q%y
END FUNCTION addpoints
END MODULE point_module
The main program would contain:
USE point_module
TYPE (point) :: px, py, pz
.
.
.
pz = addpoints(px,py)
MODULE genswap
IMPLICIT NONE
TYPE point
REAL :: x, y
END TYPE point
INTERFACE swap
MODULE PROCEDURE swapreal, swapint, swaplog, swappoint
END INTERFACE
CONTAINS
SUBROUTINE swappoint (a,b)
IMPLICIT NONE
TYPE (point), INTENT(INOUT) :: a, b
TYPE (point) :: temp
temp = a
a = b
b = temp
END SUBROUTINE swappoint
SUBROUTINE swapreal
IMPLICIT NONE
REAL, INTENT(INOUT) :: a,b
REAL :: temp
temp=a
a=b
b=temp
END SUBROUTINE swapreal
!similar subroutines for swapint and swaplog
...
END MODULE genswap
This is done by using the PRIVATE statement:
PRIVATE :: sub1, sub2
or, the PRIVATE attribute:
INTEGER,PRIVATE,SAVE :: currentrow,currentcol
INTERFACE OPERATOR (intrinsic_operator)
interace_body
END INTERFACE
For example, the `+' character could be extended for character variables in order to concatenate two strings ignoring any trailing blanks, and this could be put in a module:
MODULE operator_overloading
IMPLICIT NONE
...
INTERFACE OPERATOR (+)
MODULE PROCEDURE concat
END INTERFACE
...
CONTAINS
FUNCTION concat(cha,chb)
IMPLICIT NONE
CHARACTER (LEN=*), INTENT(IN) :: cha, chb
CHARACTER (LEN=(LEN_TRIM(cha) + LEN_TRIM(chb))) :: concat
concat = TRIM(cha)//TRIM(chb)
END FUNCTION concat
...
END MODULE operator_overloading
Now the expression `cha + chb' is meaningful in any program unit which `USES' this module.
Notice in this example the interface block. The procedure defining the operator is in a module and it is not necessary to have explicit interfaces for module procedures within the same module. An interface block, in this case, which provides a generic name or operator for a set of modules should be of the form:
INTERFACE ...
MODULE PROCEDURE list
END INTERFACE
where list is a list of the names of the module procedures concerned.
The following example shows the definition of an operator .DIST. which calculates the straight line distance between two derived type `points'. The operator has been defined within a module and so can be used by several program units.
MODULE distance_mod
...
TYPE point
REAL :: x,y
END TYPE point
...
INTERFACE OPERATOR (.DIST.)
MODULE PROCEDURE calcdist
END INTERFACE
...
CONTAINS
...
FUNCTION calcdist (px,py)
REAL :: calcdist
TYPE (point), INTENT(IN) :: px, py
calcdist = &
SQRT ((px%x-py%x)**2 + (px%y-py%y)**2 )
END FUNCTION calcdist
...
END MODULE distance_mod
The calling program will include:
USE distance_mod
TYPE(point) :: px,py
...
distance = px .DIST. py
The power of modules can be seen in the following example, as a way to define a derived type and all the associated operators:
MODULE moneytype
IMPLICIT NONE
TYPE money
INTEGER :: pounds, pence
END TYPE money
INTERFACE OPERATOR (+)
MODULE PROCEDURE addmoney
END INTERFACE
INTERFACE OPERATOR (-)
MODULE PROCEDURE negatemoney, subtractmoney
END INTERFACE
CONTAINS
FUNCTION addmoney(a,b)
TYPE (money) :: addmoney
TYPE (money), INTENT(IN) :: a,b
INTEGER :: carry, temppence
temppence = a%pence + b%pence
carry = 0
IF (temppence>100) THEN
temppence = temppence - 100
carry = 1
END IF
addmoney%pounds = a%pounds + b%pounds + carry
addmoney%pence = temppence
END FUNCTION addmoney
FUNCTION negatemoney(a)
TYPE (money) :: negatemoney
TYPE (money), INTENT(IN) :: a
negatemoney%pounds = -a%pounds
negatemoney%pence = -a%pence
END FUNCTION negatemoney
FUNCTION subtractmoney(a,b)
TYPE (money) :: subtractmoney
TYPE (money), INTENT(IN) :: a,b
INTEGER :: temppound, temppence, carry
temppence = a%pence - b%pence
temppound = a%pounds - b%pounds
! IF construct to incorporate any carry required from subtraction
IF ((temppence<0).AND.(temppound>0)) THEN
temppence = 100 + temppence
temppound = temppound - 1
ELSE IF ((temppence>0).AND.(temppound<0)) THEN
temppence = temppence - 100
temppound = temppound + 1
END IF
subtractmoney%pence = temppence
subtractmoney%pounds = temppound
END FUNCTION subtractmoney
END MODULE moneytype
For example, suppose the variables ax and px are declared as follows:
REAL :: ax
TYPE (point) :: px
and within the program the following assignment is required
ax = px
i.e type point is assigned to type real. Such an assignment is not valid until it has been defined.
Continuing with this example, suppose we require that ax takes the larger of the x and y components of px. This assignment needs to be defined via a subroutine with two non-optional arguments, the first having INTENT(OUT), the second having INTENT(IN) and an interface assignment block must be created.
The interface block required for assignment overloading is of the form
INTERFACE ASSIGNMENT (=)
subroutine_interface_body
END INTERFACE
The assignment definition could be placed in a module, as follows
MODULE assignoverload_mod
IMPLICIT NONE
TYPE point
REAL :: x, y
END TYPE point
...
INTERFACE ASSIGNMENT (=)
MODULE PROCEDURE assignnew
END INTERFACE
CONTAINS
SUBROUTINE assignnew (ax,px)
REAL, INTENT(OUT) :: ax
TYPE (point), INTENT(IN) :: px
ax = MAX(px%x,px%y)
END SUBROUTINE assignnew
...
END MODULE assignoverload_mod
The main program needs to invoke this module, with the USE statement, and the assignment type point to type real is now defined and can be used as required:
USE assignover_mod
REAL :: ax
TYPE (point) :: px
...
ax = px
A scoping unit is one of the following:
The scope of a name declared in an internal subprogram is only the subprogram itself, not other internal subprograms. The scope of the name of an internal subprogram, and of its number and type of arguments, extends throughout the containing program unit, and therefore all other internal subprograms.
The scope of a name declared in a module extends to all program units which USE that module, excluding any internal subprograms in which the name is redeclared.
Consider the scoping unit defined above:
MODULE scope1 ! scope 1
... ! scope 1
CONTAINS ! scope 1
SUBROUTINE scope2 ! scope 2
TYPE scope3 ! scope 3
... ! scope 3
END TYPE ! scope 3
INTERFACE ! scope 3
100 ... ! scope 4
END INTERFACE ! scope 3
REAL x, y ! scope 3
... ! scope 3
CONTAINS ! scope 3
FUNCTION scope5(...) ! scope 5
REAL y ! scope 5
y = x + 1.0 ! scope 5
100 ... ! scope 5
END FUNCTION scope5 ! scope 5
END SUBROUTINE scope2 ! scope 2
END MODULE scope1 ! scope 1
Structured Fortran 90 programs will consist of a main program and modules containing specifications, interfaces and procedures - external procedures no longer being required. The introduction of many new features such as derived types, overloading, internal subprograms and modules make possible the creation of sophisticated Fortran 90 code.