Extracted from   http://www.star.le.ac.uk/~cgp/prof77.html
Professional Programmer's Guide to Fortran77 (7th June 2005)
Copyright © 1988 - 2005 Clive G. Page
9.3 External Procedures

There are two forms of external procedure, both of which take the form of a complete program unit.
    * External functions, which are specified by a program unit starting
      with a FUNCTION statement. They are executed whenever the
      corresponding function is used as an operand in an expression.

    * Subroutines, which are specified by a program unit starting with a
      SUBROUTINE statement. They are executed in response to a CALL
      statement.
In either form the last statement of the program unit must be an END statement. Any other statements (except PROGRAM or BLOCK DATA statements) may be used within the program unit.
There are two statements provided especially for use in external procedures. The SAVE statement ensures that the values of local variables and arrays are preserved after the procedure returns control to the calling unit: these values will then be available if the procedure is executed subsequently. The RETURN statement may be used to terminate the execution of the procedure and cause an immediate return to the control of the calling unit. Execution of the END statement at the end of the procedure has exactly the same effect. Both of these are described in full later in the section.
Most Fortran systems also allow external procedures to be specified in languages other than Fortran: they can be called in the same way as Fortran procedures but their internal operations are, of course, beyond the scope of this book.
It is best to think of the subroutine as the more general form of procedure; the external function should be regarded as a special case for use when you only need to return a single value to the calling unit.
Here is a simple example of a procedure which converts a time of day in hours, minutes, and seconds into a count of seconds since midnight. Since only one value needs to be returned, the procedure can have the form of an external function. (In fact this is such a simple example that it would have been possible to define it as a statement function.)
*TSECS converts hours, minutes, seconds to total seconds. 
       REAL FUNCTION TSECS(NHOURS, MINS, SECS) 
       INTEGER NHOURS, MINS 
       REAL SECS 
       TSECS = ((NHOURS * 60) + MINS) * 60 + SECS 
       END 
Thus if we use a function reference like TSECS(12,30,0.0) in an expression elsewhere in the program it will convert the time to seconds since midnight (about 45000.0 seconds in this case). The items in parentheses after the function name :
(12,30,0.0)
are known as the actual arguments of the function; these values are transferred to the corresponding dummy arguments
(NHOURS, MINS, SECS)
of the procedure before it is executed. In this example the argument list is used only to transfer information into the function from outside, the function name itself returns the required value to the calling program. In subroutines, however, there is no function name to return information but the arguments can be used for transfers in either direction, or both. The rules permit them to be used in this more general way in functions, but it is a practice best avoided.
The next example performs the inverse conversion to the TSECS function. Since it has to return three values to the calling program unit the functional form is no longer appropriate, and a subroutine will be used instead.
*Subroutine HMS converts TIME in seconds into hours, mins,secs. 
      SUBROUTINE HMS(TIME, NHOURS, MINS, SECS) 
      REAL TIME, SECS 
      INTEGER NHOURS, MINS 
      NHOURS = INT(TIME / 3600.0) 
      SECS   = TIME - 3600.0 * NHOURS 
      MINS   = INT(SECS / 60.0) 
      SECS   = TIME - 60.0 * MINS 
      END 
In this case the subroutine could be executed by using a statement such as:
       CALL HMS(45000.0, NHRS, MINS, SECS) 
       WRITE(UNIT=*, FMT=*) NHRS, MINS, SECS 
Here the first argument transfers information into the subroutine, the other three are used to return the values which it calculates. You do not have to specify whether a particular argument is to transfer information in or out (or in both directions), but there are rules about the form of actual argument that you can use in each case. These are explained in full below.

Procedure Independence

Each program unit has its own independent set of symbolic names and labels. Type statements and IMPLICIT statements may be used to specify their data types.
External procedures can themselves call any other procedures and these may call others in turn, but procedure are not allowed to call themselves either directly or indirectly; that is recursive calling is not permitted in Fortran.

Information Transfer

Information can be transferred to and from an external procedure by any of three methods.
    * An argument list: as shown in the two examples above. This is the
      preferred method of interfacing as it is the most flexible and
      modular. It is described in detail in the remainder of this section.

    * Common blocks: these are lists of variables or arrays which are
      stored in areas of memory shared between two or more program
      units. They are useful in special circumstances when procedures
      have to be coupled closely together, but are otherwise less
      satisfactory. Common blocks are covered in detail in section 12.

    * External files: interfacing via external files is neither
      convenient nor efficient but it is mentioned here to point out
      that external files are global. Once a file has been opened in any
      program unit it can be accessed anywhere in the program provided
      that the appropriate I/O unit number is available. A unit number
      can be passed into a procedure as an integer argument.

Procedure Execution

It is not necessary to know how the Fortran system actually transfers information from one procedure to another to make use of the system, but the rules governing the process are somewhat complicated and it may be easier to understand them if you appreciate the basis on which they have been formulated. The rules in the Fortran Standard are based on the assumption that the address of an actual argument is transferred in each case: this may or may not be true in practice but the properties will be the same as if it is.
This means that when you reference a dummy variable or assign a new value to one you are likely to be using the memory location occupied by the actual argument. By this means even large arrays can be transferred efficiently to procedures. A slight modification of this system is needed for items of character type so that the length of the item can be transferred as well as its address.
When a function reference or CALL statement is executed any expressions in the argument list are evaluated; the addresses of the arguments are then passed to the procedure. When it returns control this automatically makes updated values available to the corresponding items in the actual argument list.

Functions with Side-effects

The rules of Fortran allow functions to have side-effects, that is to alter their actual arguments or to change other variables within common blocks. Functions with side-effects cannot be used in expressions where any of the other operands of the expression would be affected, nor can they be used in subscript or substring references when any other expression used in the same references would be affected. This rule ensures that the value of an expression cannot depend arbitrarily on the way in which the computer chooses to evaluate it.
There are also restrictions on functions which make use of input/output statements even on internal files: these cannot be used in expressions in other I/O statements. This is to avoid the I/O system being used recursively.
By far the best course is to use the subroutine form for any procedure with side-effects.

9.4 Arguments of External Procedures

Arguments can pass information into a procedure or out from it, or in both directions. This just depends on the way that the dummy argument is used within the procedure. Although any argument order is permitted, it is common practice to put input arguments first, then those that pass information both ways, and then arguments which just return information from the procedure.
The rules for argument association are the same for both forms of external procedure. The list of dummy arguments (sometimes called formal arguments) of an external procedure is specified in its FUNCTION or SUBROUTINE statement. There can be any number of arguments, including none at all. If there are no arguments then the parentheses can be omitted in the CALL and SUBROUTINE statement but not in a FUNCTION statement or function reference.
The dummy argument list is simply a list of symbolic names which can represent any mixture of
    * variables

    * arrays

    * procedures.
A name cannot, of course, appear twice in the same dummy argument list.
Dummy variables, arrays, and procedures are distinguished only by the way that they are used within the procedure. The dimension bounds of a dummy arrays must be specified in a subsequent type or DIMENSION statement; dummy procedures must appear in a CALL or EXTERNAL statement or be used in a function reference; anything else is, by elimination, a dummy argument variable.
Dummy argument variables and arrays can be used in executable statements in just the same way as local items of the same form, but they cannot appear in SAVE, COMMON, DATA, or EQUIVALENCE statements.

Argument Association

The actual arguments of the function reference or CALL statement become associated with the corresponding dummy arguments of the FUNCTION or SUBROUTINE statement. The main rules are as follows:
    * There must be the same number of actual and dummy arguments; they
      are associated solely by their position in the two lists. Optional
      arguments are not permitted in Fortran77.

    * If the dummy argument is a variable, array, or procedure used as a
      function then the corresponding actual argument must have the same
      data type.

    * If the dummy argument is an array then its array bounds must not
      be larger than those of the corresponding actual argument.
      Alternatively the dimension bounds of a dummy array can be passed
      in by means of other procedure arguments to form an adjustable
      array. This option and the assumed-size array are both described
      in section 9.6.

    * If the dummy argument is a character item then its length must not
      be greater than that of the corresponding actual argument.
      Alternatively there is a passed-length option for character
      arguments: see section 9.5.
Because program units are compiled independently, it is difficult for the compiler to check for mismatches in actual and dummy argument lists. Although mismatches could, in principle, be detected by the linker, this rarely seems to happen in practice. Errors, particularly mismatches of data type or array bounds, are especially easy to make but hard to detect. Sometimes the only indication is that the program produces the wrong answer. This shows how important it is to check procedure interfaces.

Duplicate Arguments

The same actual argument cannot be used more than once in a procedure call if the corresponding dummy arguments are assigned new values. For example, with:
       SUBROUTINE FUNNY(X, Y) 
       X = 2.0 
       Y = 3.0 
       END 
A call such as:
CALL FUNNY(A, A)
would be illegal because the system would try to assign 2.0 and 3.0 to the variable A in some unpredictable order, so one cannot be certain of the result.
A similar restriction applies to variables which are returned via a common block and also through the procedure argument list.

9.5 Variables as Dummy Arguments

If the dummy argument of a procedure is a variable and it has a value assigned to it within the procedure, then the corresponding actual argument can be:
    * a variable,

    * an array element, or

    * a character substring.
If, however, the dummy variable preserves its initial value throughout the execution then the actual argument can be any of these three forms above or alternatively:
    * an expression of any form (including a constant).
The reason for this restrictions is easy to see by considering the ways of calling the subroutine SILLY in the next example:
       SUBROUTINE SILLY(N, M) 
       N = N + M 
       END 
If it is called with a statement such as:
       NUMBER = 10 
       CALL SILLY(NUMBER, 5) 
then the value of NUMBER will be updated to 15 as a result of the call. But it is illegal to call the function with a constant as the first argument, thus:
       CALL SILLY(10, 7) 
because on exit the subroutine will attempt to return the value of 17 to the actual argument which was specified as the constant ten. The effects of committing such an error are system-dependent. Some systems detect the attempt to over-write a constant and issue an error message; others ignore the attempt and allow the program to continue; but some systems will actually go ahead and over-write the constant with a new value, so that if you use the constant 10 in some subsequent statement in the program you may get a value of 17. Since this can have very puzzling effects and be hard to diagnose, it is important to avoid doing this inadvertently.
If you make use of procedures written by other people you may be worried about unintentional effects of this sort. In principle it should be possible to prevent a procedure altering a constant argument by turning each one into an expression, for example like this:
CALL SILLY(+10, +5)
or
CALL SILLY((10), (5))
Although either of these forms should protect the constants, it is still against the rules of Fortran for the procedure to attempt to alter the values of the corresponding dummy arguments. You will have to judge whether it is better to break the rules of the language than to risk corrupting a constant.

Expressions, Subscripts, and Substrings

If the actual argument contains expressions then these are evaluated before the procedure starts to execute; even if the procedure later modifies operands of the expression this has no effect on the value passed to the dummy argument. The same rule applies to array subscript and character substring expressions. For example, if the procedure call consists of:
CALL SUB( ARRAY(N), N, SIN(4.0*N), TEXT(1:N) )
and the procedure assigns a new value to the second argument, N, during its execution, it has no effect on the other arguments which all use the original value of N. The updated value of N will, of course, be passed back to the calling unit.

Passed-length Character Arguments

A character dummy argument will have its length set automatically to that of the corresponding actual argument if the special length specification of *(*) is used.
To illustrate this, here is a procedure to count the number of vowels in a character string. It uses the intrinsic function LEN to determine the length of its dummy argument, and the INDEX function to see whether each character in turn is in the set ``AEIOU'' or not.
       INTEGER FUNCTION VOWELS(STRING) 
       CHARACTER*(*) STRING 
       VOWELS = 0 
       DO 25, K = 1,LEN(STRING) 
          IF( INDEX('AEIOU', STRING(K:K)) .NE. 0) THEN 
               VOWELS = VOWELS + 1 
          END IF 
25     CONTINUE 
       END 
Note that the function has a data type which is not the default for its initial letter so that it will usually be necessary to specify its name in a INTEGER statement in each program unit which references the function.
This passed-length mechanism is recommended not only for general-purpose software where the actual argument lengths are unknown, but in all cases unless there is a good reason to specify a dummy argument of fixed length.
There is one restriction on dummy arguments with passed length: they cannot be operands of the concatenation operator (//) except in assignment statements. Note that the same form of length specification ``*(*)'' can be used for named character constants but with a completely different meaning: named constants are not subject to this restriction.

9.6 Arrays as Arguments

If the dummy argument of a procedure is an array then the actual argument can be either:
    * an array name (without subscripts)

    * an array element.
The first form transfers the entire array; the second form, which just transfers a section starting at the specified element, is described in more detail further on.
The simplest, and most common, requirement is to make the entire contents of an array available in a procedure. If the actual argument arrays are always going to be the same size then the dummy arrays in the procedure can use fixed bounds. For example:
       SUBROUTINE DOT(X, Y, Z) 
*Computes the dot product of arrays X and Y of 100 elements 
* producing array Z of the same size. 
       REAL X(100), Y(100), Z(100) 
       DO 15, I = 1,100 
          Z(I) = X(I) * Y(I) 
15     CONTINUE 
       END 
This procedure could be used within a program unit like this:
       PROGRAM PROD 
       REAL A(100), B(100), C(100) 
       READ(UNIT=*,FMT=*)A,B 
       CALL DOT(A, B, C) 
       WRITE(UNIT=*,FMT=*)C 
       END 
This is perfectly legitimate, if inflexible, since it will not work on arrays of any other size.

Adjustable Arrays

A more satisfactory solution is to generalise the procedure so that it can be used on arrays of any size. This is done by using an adjustable arrays declaration. Here the operands in each dimension bound expression may include integer variables which are also arguments of the procedure (or members of a common block). The following example shows how this may be done:
       SUBROUTINE DOTPRO(NPTS, X, Y, Z) 
       REAL X(NPTS), Y(NPTS), Z(NPTS) 
       DO 15, I = 1,NPTS 
* etc. 
In this case the calling sequence would be something like:
CALL DOTPRO(100, A, B, C)
An adjustable array declaration is permitted only for arrays which are dummy arguments, since the actual array space has in this case already been allocated in the calling unit or at some higher level. The method can be extended in the obvious way to cover multi-dimensional arrays and those with upper and lower bounds, for example:
       SUBROUTINE MULTI(MAP, K1, L1, K2, L2, TRACE) 
       DOUBLE PRECISION MAP(K1:L1, K2:L2) 
       REAL TRACE(L1-K1+1) 
The adjustable array mechanism can, of course, be used for arrays of any data type; an adjustable array can also be passed as an actual argument of a procedure with, if necessary, the array bounds passed on in parallel.
Each array bound of a dummy argument array may be an integer expression involving not only constants but also integer variables passed in to the procedure either as arguments or by means of a common block. The extent of each dimension of the array must not be less than one and must not be greater than the extent of the corresponding dimension of the actual argument array.
If any integer variable (or named constant) used in an array-bound expression has a name which does not imply integer type then the INTEGER statement which specifies its type must precede its use in a dimension-bound expression.

Assumed-size Arrays

There may be circumstances in which it is impracticable to use either fixed or adjustable array declarations in a procedure because the actual size of the array is unknown when the procedure starts executing. In this case an assumed-size array is a viable alternative. These are also only permitted for dummy argument arrays of procedures, but here the array is, effectively, declared to be of unknown or indefinite size. For example:
       REAL FUNCTION ADDTWO(TABLE, ANGLE)  
       REAL TABLE(*) 
       N = MAX(1, NINT(SIN(ANGLE) * 500.0)) 
       ADDTWO = TABLE(N) + TABLE(N+1) 
       END 
Here the procedure only knows that array TABLE is one-dimensional with a lower-bound of one: that is all it needs to know to access the appropriate elements N and N+1. In executing the procedure it is our responsibility to ensure that the value of ANGLE will never result in an array subscript which is out of range. This is always a danger with assumed-size arrays. Because the compiler does not have any information about the upper-bound of an assumed-size array it cannot use any array-bound checking code even if it is normally able to do this. An assumed-size array can only have the upper-bound of its last dimension specified by an asterisk, all the other bounds (if any) must conform to the normal rules (or be adjustable using integer arguments).
An assumed size dummy argument array is specified with an asterisk as the upper bound of its last (or only) dimension. All the other dimension bounds, if any, must conform to normal rules for local arrays or adjustable arrays.
There is one important restriction on assumed size arrays: they cannot be used without subscripts in I/O statements, for example in the input list of a READ statement or the output list of a WRITE statement. This is because the compiler has no information about the total size of the array when compiling the procedure.

Array Sections

The rules of Fortran require that the extent of an array (in each dimension if it is multi-dimensional) must be at least as large in the actual argument as in the dummy argument, but they do not require actual agreement of both lower and upper bounds. For example:
       PROGRAM CONFUS 
       REAL X(-1:50), Y(10:1000) 
       READ(UNIT=*,FMT=*) X, Y 
       CALL OUTPUT(X) 
       CALL OUTPUT(Y) 
       END 

       SUBROUTINE OUTPUT(ARRAY) 
       REAL ARRAY(50) 
       WRITE(UNIT=*,FMT=*) ARRAY 
       END 
The effect of this program will be to output the elements X(-1) to X(48) since X(48) corresponds to ARRAY(50), and then output Y(10) to Y(59) also. The subroutine will work similarly on a slice through a two-dimensional array:
       PROGRAM TWODIM 
       REAL D(100,20) 
* ... 
       NSLICE = 15 
       CALL OUTPUT(D(1,NSLICE)) 
In this example the slice of the array from elements D(1,15) to D(50,15) will be written to the output file. In order to work out what is going to happen you need to know that Fortran arrays are stored with the first subscript most rapidly varying, and that the argument association operates as if the address of the specified element were transferred to the base address of the dummy argument array.
The use of an array element as an actual argument when the dummy argument is a complete array is a very misleading notation and the transfer of array sections should be avoided if at all possible.

Character Arrays

When a dummy argument is a character array the passed-length mechanism can be used in the same way as for a character variable. Every element of the dummy array has the length that was passed in from the actual argument.
For example, a subroutine designed to sort an array of character strings into ascending order might start with specification statements like these:
       SUBROUTINE SORT(NELS, NAMES) 
       INTEGER NELS 
       CHARACTER NAMES(NELS)*(*) 
Alternatively the actual argument can be a character variable or substring. In such cases it usually makes more sense not to use the passed-length mechanism. For example an actual argument declared:
CHARACTER*80 LINE
could be passed to a subroutine which declared it as an array of four 20-character elements:
       SUBROUTINE SPLIT(LINE) 
       CHARACTER LINE(4)*20 
Although this is valid Fortran, it is not a very satisfactory programming technique to use a procedure call to alter the shape of an item so radically.

9.7 Procedures as Arguments

Fortran allows one procedure to be used as the actual argument of another procedure. This provides a powerful facility, though one that most programmers use only rarely. Procedures are normally used to carry out a given set of operations on different sets of data; but sometimes you want to carry out the same set of operations on different functional forms. Examples include: finding the gradient of a function, integrating the area under a curve, or simply plotting a graph. If the curve is specified as a set of data points then you can simply pass over an array, but if it is specified by means of some algorithm then the procedure which evaluates it can itself be an actual argument.
In the next example, the subroutine GRAPH plots a graph of a function MYFUNC between specified limits, with its argument range divided somewhat arbitrarily into 101 points. For simplicity it assumes the existence of a subroutine PLOT which moves the pen to position (X,Y). Some other subroutines would, in practice, almost certainly be required.
      SUBROUTINE GRAPH(MYFUNC, XMIN, XMAX) 
*Plots functional form of MYFUNC(X) with X in range XMIN:XMAX. 
      REAL MYFUNC, XMIN, XMAX 
      XDELTA = (XMAX - XMIN) / 100.0 
      DO 25, I = 0,100 
          X = XMIN + I * XDELTA 
          Y = MYFUNC(X) 
          CALL PLOT(X, Y) 
25    CONTINUE 
      END 
The procedure GRAPH can then be used to plot a function simply by providing its name them as the first argument of the call. The only other requirement is that the name of each function used as an actual argument in this way must be specified in an INTRINSIC or EXTERNAL statement, as appropriate. Thus:
       PROGRAM CURVES 
       INTRINSIC SIN, TAN 
       EXTERNAL MESSY  
       CALL GRAPH(SIN, 0.0, 3.14159) 
       CALL GRAPH(TAN, 0.0, 0.5) 
       CALL GRAPH(MESSY, 0.1, 0.9) 
       END 

       REAL FUNCTION MESSY(X) 
       MESSY = COS(0.1*X) + 0.02 * SIN(SQRT(X))  
       END 
This will first plot a graph of the sine function, then of the tangent function with a different range, and finally produce another plot of the external function called MESSY. These functions must, of course, have the same procedure interface themselves and must be called correctly in the GRAPH procedure.
It is possible to pass either a function or a subroutine as an actual argument in this way: the only difference is that a CALL statement is used instead of a function reference to execute the dummy procedure. It is possible to pass a procedure through more than one level of procedure call in the same way. Continuing the last example, another level could be introduced like this:
       PROGRAM CURVE2 
       EXTERNAL MESSY 
       INTRINSIC SIN, TAN 
       CALL GRAPH2(PRETTY) 
       CALL GRAPH2(TAN) 
       END 

       SUBROUTINE GRAPH2(PROC) 
       EXTERNAL PROC 
       CALL GRAPH(PROC, 0.1, 0.7) 
       END 
Thus the procedure GRAPH2 sets limits to each plot and passes the procedure name on to GRAPH. The symbolic name PROC must be declared in an EXTERNAL statement as it is a dummy procedure: an EXTERNAL statement is required whether the actual procedure at the top level is intrinsic or external. The syntax of the INTRINSIC and EXTERNAL statements is given in section 9.12 below.
The name of an intrinsic function used as an actual argument must be a specific name and not a generic one. This is the only circumstance in which you still have to use specific names for intrinsic functions. A full list of specific names is given in the appendix. A few of the most basic intrinsic functions which are often expanded to in-line code (those for type conversion, lexical comparison, as well as MIN and MAX) cannot be passed as actual arguments.

9.8 Subroutine and Call Statements

It is convenient to describe these two statements together as they have to be closely matched in use. The general form of the SUBROUTINE statement is:
SUBROUTINE /name/ ( /dummy1,/ /dummy2,/ ... /dummyN/ )
or
SUBROUTINE /name/
The second form just indicates that if there are no arguments then the parentheses are optional.
The symbolic name of the subroutine becomes a global name; it must not be used at all within the program unit and must not be used for any other global item within the entire executable program.
The dummy arguments are also simply symbolic names. The way in which these are interpreted is covered in the next section.
The CALL statement has similar general forms:
CALL /name/ ( /arg1,/ /arg2,/ ... / argN/ )
or
CALL /name/
Again, if there are no arguments the parentheses are optional.
The name must be that of a subroutine (or dummy subroutine). Each arg is an actual argument which can be a variable, array, substring, array element or any form of expression. The permitted forms, which depend on the form of the corresponding dummy argument and how it is used within the subroutine, are fully described in the preceding sections.

9.9 RETURN Statement

The RETURN statement just consists of the keyword
RETURN
Its effect is to stop the procedure executing and to return control, and where appropriate argument and function values, to the calling program unit. The execution of the END statement at the end of the program unit has the exactly the same effect, so that RETURN is superfluous in procedures which have only one entry and one exit point (as all well-designed procedures should). It is, however, sometimes convenient to use RETURN for an emergency exit. Here is a somewhat simple-minded example just to illustrate the point:
     REAL FUNCTION HYPOT(X, Y) 
*Computes the hypotenuse of a right-angled triangle. 
      REAL X, Y 
      IF(X .LE. 0.0 .OR. Y .LE. 0.0) THEN 
          WRITE(UNIT=*,FMT=*)'Warning: impossible values' 
          HYPOT = 0.0 
          RETURN 
      END IF 
      HYPOT = SQRT(X**2 + Y**2) 
      END 
This function could be used in another program unit like this:
       X = HYPOT(12.0, 5.0) 
       Y = HYPOT(0.0, 5.0) 
which would assign to X the value of 13.0000 approximately, while the second function call would cause a warning message to be issued and would return a value of zero to Y.
In the external function shown above it would have been perfectly possible to avoid having two exits points by an alternative ending to the procedure, such as:
      IF(X .LE. 0.0 .OR. Y .LE. 0.0) THEN 
          WRITE(UNIT=*,FMT=*)'Warning: impossible values' 
          HYPOT = 0.0 
      ELSE  
          HYPOT = SQRT(X**2 + Y**2) 
      END IF 
      END 
In more realistic cases, however, the main part of the calculation would be much longer than just one statement and it might then be easier to understand the working if a RETURN statement were to be used than with almost all of the procedure contained within an ELSE-block. A third possibility for emergency exits is to use an unconditional GO TO statement to jump to a label placed on the END statement.

9.10 FUNCTION Statement

The FUNCTION statement must be the first statement of every external function. Its general form is:
/type / FUNCTION( /dummy1,/ /dummy2,/ ... /dummyN/ )
The /type/ specification is optional: if it is omitted then the type of the result is determined by the usual rules. The function name may have its type specified by a type or IMPLICIT statement which appears later in the program unit. If the function is of type character then the length may be specified by a literal constant (but not a named constant) or may be given in the form CHARACTER*(*) in which case the length will be passed in as the length declared for the function name in the calling program unit.
There may be any number of dummy arguments including none, but the parentheses must still be present. Dummy arguments may, as described in section 9.4, be variables, arrays, or procedures.
The function name may be used as a variable within the function subprogram unit; a value must be assigned to this variable before the procedure returns control to the calling unit. If the function name used the passed-length option then the corresponding variable cannot be used as an operand of the concatenation operator except in an assignment statement. The passed-length option is less useful for character functions than for arguments because the length is inevitably the same for all references from the same program unit. For example:
       PROGRAM FLEX 
       CHARACTER CODE*8, CLASS*6, TITLE*16  
       CLASS = CODE('SECRET') 
       TITLE = CODE('ORDER OF BATTLE') 
       END 

       CHARACTER*(*) FUNCTION CODE(WORD) 
       CHARACTER WORD*(*), BUFFER*80 
       DO 15, K = 1,LEN(WORD) 
            BUFFER(K:K) = CHAR(ICHAR(WORD(K:K) + 1) 
15     CONTINUE 
       CODE = BUFFER 
       END 
Unfortunately, although this function can take in an argument of any length up to 80 characters long and encode it, it can only return a result of exactly 8 characters long when called from the program FLEX, so that it will not produce the desired result when provided with the longer character string. This limitation could be overcome with the use of a subroutine with a second passed-length argument to handle the returned value.
Functions without arguments do not have a wide range of uses but applications for them do occur up from time to time, for example when generating random numbers or reading values from an input file. For example:
       PROGRAM COPY 
       REAL NEXT 
       DO 10,I = 1,100 
             WRITE(UNIT=*,FMT=*) NEXT() 
10     CONTINUE 
       END 

       REAL FUNCTION NEXT()  
       READ(UNIT=*,FMT=*) NEXT  
       END 
The parentheses are needed on the function call to distinguish it from a variable. The function statement itself also has to have the empty pair of parentheses, presumably to match the call.

9.11 SAVE Statement

SAVE is a specification statement which can be used to ensure that variables and arrays used within a procedure preserve their values between successive calls to the procedure. Under normal circumstances local items will become ``undefined'' as soon as the procedure returns control to the calling unit. It is often useful to store the values of certain items used on one call to avoid doing extra work on the next. For example:
       SUBROUTINE EXTRA(MILES) 
       INTEGER MILES, LAST 
       SAVE LAST 
       DATA LAST /0/ 
       WRITE(UNIT=*, FMT=*) MILES - LAST, ' more miles.' 
       LAST = MILES 
       END 
This subroutine simply saves the value of the argument MILES each time and subtracts it from the next one, so that it can print out the incremental value. The value of LAST had to be given an initial value using a DATA statement in order to prevent its use with an undefined value on the initial call.
Local variables and arrays and complete named common blocks can be saved using SAVE statements, but not variables and arrays which are dummy arguments or which appear within common blocks.
Items which are initially defined with a DATA statement but which are never updated with a new value do not need to be saved.
The SAVE statement has two alternative forms:
SAVE /item, item, ... item/
SAVE
Where each /item/ can be a local variable or (unsubscripted) array, or the name of a common block enclosed in slashes. The second form, with no list of items, saves all the allowable items in the program unit. This form should not be used in any program unit which uses a common block unless all common blocks used in that program unit are also used in the main program or saved in every program unit in which it appears. The SAVE statement can be used in the main program unit (so that it could be packaged with other specifications in an INCLUDE file) but has no effect.
Many current Fortran systems have a simple static storage allocation scheme in which all variables are saved whether SAVE is used or not. But on small computers which make use of disc overlays, or large ones with virtual memory systems, this may not be so. You should always take care to use the SAVE statement anywhere that its use is indicated to make your programs safe and portable. Even where it is at present strictly redundant it still indicates to the reader that the procedure works by retaining information from one call to the next, and this is valuable in itself.

9.12 EXTERNAL and INTRINSIC Statements

The EXTERNAL statement is used to name external procedures which are required in order to run a given program unit. It may specify the name of any external function or subroutine. It is required in three rather different circumstances:
    * whenever an external procedure or dummy procedure is used as the
      actual argument of another procedure call;

    * to call any procedure which has a name duplicating an intrinsic
      function;

    * to ensure that a named block data subprogram is linked into the
      complete executable program. This specialised use is covered
      further in section 12.4.
The INTRINSIC statement is used to declare a name to be that of an intrinsic function. It is normally necessary only when that function is to be used as the actual argument of another procedure call, but may also be advisable when calling a non-standard intrinsic function to remove any ambiguity which might arise if an external function of the same name also existed.
The general form of the two statements is the same:
EXTERNAL /ename,/ /ename,/ ... /ename/
INTRINSIC /iname,/ /iname,/ ... /iname/
Where /ename/ can be the name of an external function or subroutine or a dummy procedure; /iname/ must be specific name of an intrinsic function. For example, to use the real and double precision versions of the trigonometric functions as actual arguments we need: INTRINSIC SIN, COS, TAN, DCOS, DSIN, DTAN When the function name SIN is used as an actual argument it refers to the specific real sine function; in other contexts it still has its usual generic property. The use of procedures as actual arguments is covered in detail in section 9.7; a list of specific names of intrinsic functions is given in the appendix.