%In order to discuss this topic we need some definitions. In logical terms, an executable program consists of one main program and zero or more subprograms (or procedures) - these do something. Subprograms are either functions or subroutines, which are either external, internal or module subroutines. (External subroutines are what we know from FORTRAN 77.)
From an organizational point of view, however, a complete program consists of program units. These are either main programs, external subprograms or modules and can be separately compiled.
An internal subprogram is one contained in another (at a maximum of one level of nesting) and provides a replacement for the statement function:
SUBROUTINE outer
REAL x, y
:
CONTAINS
SUBROUTINE inner
REAL y
y = x + 1.
:
END SUBROUTINE inner ! SUBROUTINE mandatory
END SUBROUTINE outer
We say that outer is the host of inner, and that
inner obtains access to entities in outer by host association
(e.g. to x), whereas y is a local variable to inner.
The scope of a named entity is a scoping unit,
here outer less inner, and inner.
The names of program units and external procedures are global, and the names of implied-DO variables have a scope of the statement that contains them.
MODULE interval_arithmetic
TYPE interval
REAL lower, upper
END TYPE interval
INTERFACE OPERATOR(+)
MODULE PROCEDURE add_intervals
END INTERFACE
:
CONTAINS
FUNCTION add_intervals(a,b)
TYPE(interval), INTENT(IN) :: a, b
TYPE(interval) add_intervals
add_intervals%lower = a%lower + b%lower
add_intervals%upper = a%upper + b%upper
END FUNCTION add_intervals ! FUNCTION mandatory
:
END MODULE interval_arithmetic
and the simple statement
USE interval_arithmeticprovides use association to all the module's entities. Module subprograms may, in turn, contain internal subprograms.
We may specify the intent of dummy arguments :
SUBROUTINE shuffle (ncards, cards)
INTEGER, INTENT(IN) :: ncards ! input values
INTEGER, INTENT(OUT), DIMENSION(ncards) :: cards ! output values
Also, INOUT is possible: here the
actual argument
must be a variable
(unlike the default case where it may be a constant).
Arguments may be optional:
SUBROUTINE mincon(n, f, x, upper, lower, equalities, inequalities, convex, xstart)
REAL, OPTIONAL, DIMENSION :: upper, lower
.
.
allows us to call mincon by
CALL mincon (n, f, x, upper)and in mincon we have someting like:
IF (PRESENT(lower)) THEN ! test for presence of actual argumentArguments may be keyword rather than positional (which come first):
CALL mincon(n, f, x, equalities=0, xstart=x0)Optional and keyword arguments are handled by explicit interfaces, that is with internal or module procedures or with interface blocks .
Any reference to an internal or module subprogram is through an interface that is ``explicit'' (that is, the compiler can see all the details). A reference to an external (or dummy) procedure is usually ``implicit'' (the compiler assumes the details). However, we can provide an explicit interface in this case too. It is a copy of the header, specifications and END statement of the procedure concerned, either placed in a module or inserted directly:
REAL FUNCTION minimum(a, b, func)
! returns the minimum value of the function func(x) in the interval (a,b)
REAL, INTENT(in) :: a, b
INTERFACE
REAL FUNCTION func(x)
REAL, INTENT(IN) :: x
END FUNCTION func
END INTERFACE
REAL f,x
:
f = func(x) ! invocation of the user function.
:
END FUNCTION minimum
An explicit interface is obligatory for:
optional and keyword arguments,
POINTER and TARGET arguments (see later article),
a POINTER function result (later) and new-style array arguments and array functions (later).
It allows full checks at compile time between actual and dummy arguments.
Interface blocks provide the mechanism by which we are able to define generic names for specific procedures:
INTERFACE gamma ! generic name
FUNCTION sgamma(X) ! specific name for low precision
REAL (SELECTED_REAL_KIND( 6)) sgamma, x
END
FUNCTION dgamma(X) ! specific name for high precision
REAL (SELECTED_REAL_KIND(12)) dgamma, x
END
END INTERFACE
where a given set of specific names corresponding to a generic name
must all be of functions or all of subroutines.
We can use existing names, e.g. SIN, and the compiler sorts out the correct association.
We have already seen the
use of interface blocks for defined operators and assignment
(see Part
).
Indirect recursion is useful for multi-dimensional integration. To calculate
volume = integrate(fy, ybounds)we might have
RECURSIVE FUNCTION integrate(f, bounds)
! Integrate f(x) from bounds(1) to bounds(2)
REAL integrate
INTERFACE
FUNCTION f(x)
REAL f, x
END FUNCTION f
END INTERFACE
REAL, DIMENSION(2), INTENT(IN) :: bounds
:
END FUNCTION integrate
and to integrate f(x, y) over a rectangle
FUNCTION fy(y)
USE func ! module func contains function f
REAL fy, y
yval = y
fy = integrate(f, xbounds)
END
Direct recursion is when a procedure calls itself, as in
RECURSIVE FUNCTION factorial(n) RESULT(res)
INTEGER res, n
IF(n.EQ.1) THEN
res = 1
ELSE
res = n*factorial(n-1)
END IF
END
Here, we note the RESULT clause and termination test.