[comp.lang.fortran] f88 summary

khb@chiba.Sun.COM (Keith Bierman - SPD Languages Marketing -- MTS) (06/13/89)

Prof. Meissner's summary from FF, always a good source of Fortran information. 


                            SUMMARY OF FORTRAN 88
 
                            by Loren P. Meissner
                         University of San Francisco
 
              Copyright 1989 Assciation for Computing Machinery
                    (Fortran Forum 8:2 SN 21, May 1989)
Permission to copy without fee all or part of this material is granted pro-
vided that the copies are not made or distributed for direct commercial advan-
tage, the ACM copyright notice and the title of the publication and its date
appear, and notice is given that copying is by permission of the Association
for Computing Machinery.  To copy otherwise, or to republish, requires a fee
and/or specific permission.
 
    The first part of this Fortran 88 Summary, through Section 4 in the fol-
lowing outline, appears in this issue.  The next issue of Fortran Forum will
continue with new features in the area of Data Types (including Structures and
Arrays).
 
                       PART I.  OVERVIEW OF FORTRAN 88
 
Fortran 88 augments Fortran 77 with new features that are similar to those of
other modern programming languages, as well as novel features for improved
numerical computation and for more efficient array processing on parallel
architectures.  The principal enhancements to Fortran 77 may be outlined as
follows:
 
    1.  Source form
            Longer identifiers
            In-line comments and multi-statement lines
            Symbolic relational operators
            INCLUDE
            Optional free form
                Significant blanks
 
    2.  Procedures
            Internal procedures
                Nested scoping (1 level)
            Recursion
            RESULT name
            Modules
                Contain data and procedure declarations
                Nested scoping (2 levels)
                Accessibility (PUBLIC, PRIVATE) and USE
            Explicit interface
            Optional and keyword arguments
            New intrinsic procedures
                Numeric and array inquiry operations
                Bit operations (MIL-STD 1753) on integers
                More character operations
                Many array operations
                Random
                Date and Time
 
    3.  Control structure enhancements
            Block-DO
                Count-control (traditional Fortran DO control)
                DO WHILE
                DO (forever)
                EXIT and CYCLE
            END DO and unlabelled DO loops
            CASE
 
    4.  Input and Output
            Non-advancing (stop in the middle of a record)
            OPEN specifiers for POSITION, ACTION, DELIM, PAD
            Input data count
                NULLS for list-directed
                SIZE for non-advancing
            Namelist
            Whole-array; whole-structure (if no POINTER components)
            New edit descriptors
                BOZ integers
                EN ("base 1000") output
                G extended to character and logical
 
    5.  Data types, including structures and arrays
    5.1.    Parameterized intrinsic types (KIND type parameter)
                Real precision
                    Parameterized double precision
                    Complex
                Logical (permits "packed" implementation)
                Integer
    5.2.    Integers as bits
                Transfer (without type conversion)
                Bit operations (MIL-STD 1753)
                BOZ (binary, octal, hexadecimal) integer constants
    5.3.    Attribute specifiers in type declarations
                Kind type parameter
                Array rank and shape (DIMENSION)
                Initial Definition, PARAMETER, SAVE
                POINTER, TARGET, ALLOCATABLE
                Accessibility (PUBLIC, PRIVATE)
                    of Module objects and definitions
                Dummy argument INTENT (IN, OUT, IN OUT), OPTIONAL
                Procedure EXTERNAL, INTRINSIC
                Attribute specification statements
    5.4.    Derived types
                Structures (derived-type data objects)
                    Multi-level
                    Component selection
                    Whole-structure assignment
                Derived-type operations
                    Structure-valued functions
                Structure constants ("constructors")
    5.5.    Pointers
                Automatic dereferencing (no "up arrow" operator needed)
                    except in assignment and I/O of whole structures
                Pointer assignment operator "=>"
                ALLOCATE, DEALLOCATE, NULLIFY
                    No "nil" pointer constant
    5.6.    Character strings
                Alternative string delimiters
                Null strings
                Substring of constant
                New intrinsic functions
    5.7.    Arrays
                Whole-array operations
                    Extension of all scalar intrinsic operations and functions
                Array sections
                    Triplet subscript
                    Vector subscript
                Array constants ("constructors")
                Many new intrinsic functions
                Array-valued functions (user-defined)
                Automatic arrays (Stack-allocated)
                    Shape defined by dummy argument values
                Allocatable arrays (Heap-allocated)
                    Shape defined in ALLOCATE statement
                Assumed size arrays (Reshape, as in Fortran 77)
 
                            OBSOLESCENT FEATURES
 
    All of Fortran 77 remains as a proper subset of Fortran 88.  However, a
few features are marked as "obsolescent", meaning that they are candidates
for deletion from a future Fortran language standard.  For each of these
features, there is already a better alternative in Fortran 77.
        Arithmetic IF
        Real and double precision DO variables and DO parameters
        Multiple DO loops ending on the same statement, and DO loop
            termination on an action statement (e.g., assignment)
        Branch to END IF from outside its IF block
        Alternate return
        PAUSE
        ASSIGN, assigned GO TO, and assigned FORMAT statement label
 
                               1  SOURCE FORM
 
Longer Identifiers
 
An identifier in Fortran 88 may be up to 31 characters long.  The first
character must be a letter, and the remaining characters (if any) are letters,
digits, or underscore.  All characters of the identifier are significant in
distinguishing between different identifiers.  Fortran 88 does not require
that a processor support lower-case characters, but if they are permitted they
must be treated as equivalent to upper-case except in character data.  The
first two identifiers below are the same; the third is different from the
first two:
        LONG_IDENTIFIER_ENDING_WITH_A
        Long_Identifier_Ending_With_A
        Long_Identifier_Ending_With_B
        Supercalifragilisticexpialidocx
        A234567890123456789012345678901
 
In-line Comments and Multi-Statement Lines
 
The "!" character on a statement line (except in a character string) acts as a
line terminator.  Thus any characters on the line following the "!" are
comments.  The statement may be continued on the following line.  A ";"
character may be used to separate statements or partial statements on a line.
        Temp = X; X = Y; Y = Temp       ! Swap X and Y using Temp.
 
Symbolic Relational Operators
 
The following symbols may be used as alternative syntax for the "dot form" of
relational operators.  Note that no symbolic forms have been defined for:
.EQV. .NEQV. .AND. .OR. .NOT. .TRUE. .FALSE.
        ==  .EQ.        <   .LT.        >   .GT.
        <>  .NE.        <=  .LE.        >=  .GE.
 
        IF (I == 1) THEN; I = 2; ELSE IF (I >= 2) THEN; I = 1; END IF
 
Optional Free Form
 
A Fortran program unit maybe written in free form rather than the traditional
fixed form.  The two forms must not be mixed in the same program unit.
 
    Free-form lines may be as long as 132 characters, and a statement may
appear anywhere within the line.  Statement continuation is denoted by "&" on
the line to be continued, which may be followed by "!" and an in-line comment.
(Some special rules apply when a character constant is to be continued.)  The
";" statement separator is permitted.
 
    A sequence of digits at the beginning of a statement is a label.  (The
label is not separated from the rest of the statement by a ":" or otherwise.
Note that an unlabelled statement in Fortran 77, as well as in Fortran 88,
always begins with a letter.)  A ";" statement separator in free form may be
followed by a label.
 
    Blank characters are significant in free form.  A blank may appear between
lexical tokens (i.e., keywords, identifiers, constants, operators, labels, or
delimiters), but not within a token.  A blank is REQUIRED between two adjacent
tokens if both are keywords, identifiers, constants, or labels.  Certain
two-word keywords may also be written as one word, namely:
    --  Any two-word keyword that begins with END or ELSE;
    --  BLOCK DATA, DOUBLE PRECISION, GO TO, IN OUT, and SELECT CASE.
 
Source Text INCLUDE
 
An INCLUDE line may be used to insert source text from an external file into a
program.  The inserted text may also contain INCLUDE lines, which may be
nested to any level.  The text ultimately inserted must not begin nor end in
the middle of a statement.
 
                                2  PROCEDURES
 
Internal procedures
 
Internal subprograms that describe function or subroutine procedures may
appear within a subprogram, which is called the host of the internal
procedure.  Internal subprograms appear at the end of the host subprogram; a
CONTAINS statement separates them from the main part of the host subprogram.
Internal subprograms are permitted at only one level of nesting:  i.e., an
internal subprogram cannot contain further internal subprograms.
 
    An internal procedure may be invoked in an executable statement anywhere
in the host subprogram, including other internal procedures.  The name of an
internal procedure is not accessible outside the host.  Use of an internal
procedure name as an actual argument is prohibited.
 
    An internal procedure may "inherit" any name known in the host procedure,
except for dummy arguments (and the function result) of the internal procedure
and other names whose attributes are declared within the internal procedure.
A name is inherited from a host subprogram only if none of its attributes,
including type, are declared in the internal procedure.  The attributes are
those specified in the host subprogram.  If any of the attributes are declared
in the internal procedure, the name is not inherited from the host and unspec-
ified attributes assume default values in the usual way.
        PROGRAM Binomial
          IMPLICIT NONE
          INTEGER N, R, Factorial
          READ *, N, R
          PRINT *, ' N =', N, ' R =', R, ' C =' &
            , Factorial (N) / (Factorial (R) * Factorial (N - R))
          CONTAINS
          INTEGER FUNCTION Factorial (K)        ! Iterative version.
            INTEGER K, I
            Factorial = 1
            DO, I = 2, K
              Factorial = Factorial * I
            END DO
          END FUNCTION Factorial
        END PROGRAM Binomial
 
Recursion
 
Procedures, including internal procedures, may be declared to be RECURSIVE.  A
recursive procedure may invoke itself directly, or indirectly by means of
other intermediate procedures.
        PROGRAM Binomial
          IMPLICIT NONE
          INTEGER N, R, Factorial
          READ *, N, R
          PRINT *, ' N =', N, ' R =', R, ' C =' &
            , Factorial (N) / (Factorial (R) * Factorial (N - R))
          CONTAINS
          RECURSIVE INTEGER FUNCTION Factorial (K) RESULT Value
            ! See RESULT Name, below.  Value has same type as Factorial.
            INTEGER K
            IF (K <= 1) THEN
              Value = 1
            ELSE
              Value = K * Factorial (K - 1)     ! Recursive call
            END IF
          END FUNCTION Factorial
        END PROGRAM Binomial
 
    It is assumed that a Fortran 88 implementation has access to a memory man-
agement system that provides some form of "activation record" stack with a new
activation record for each new instance of the recursive procedure.  (A stack
storage discipline is appropriate because procedure calls are always "last in
first out".)  Such an activation record would contain space for:
    --  Information to permit resumption of the execution sequence after the
        point from which the procedure was invoked;
    --  The value of the function result (if the procedure is a function);
    --  Values of, or reference (inaccessible pointer) information for, dummy
        arguments;
    --  Values of local data objects (except objects with the SAVE attribute
        which are stored statically, and heap-allocated objects including
        pointer targets and allocated arrays).
 
    When a reference to a variable is executed, the storage for that variable
must be located.  This process is complicated by the possibility that a varia-
ble referenced in an internal procedure may have been "inherited" from the
host procedure, in which case the storage for the variable is in the activa-
tion record of the host rather than in the activation record of the currently
executing internal procedure.  The activation record for the host procedure is
not necessarily adjacent on the stack: a sequence of intermediate calls,
including recursive calls of the current internal procedure, might have inter-
vened.  A well-known stack management system for recursive procedures with
inheritance requires a table (called the "display") containing the location of
the currently active activation record at each level of procedure nesting.
Because internal procedure nesting (data name inheritance) in Fortran 88 is
limited to one level, this table reduces to a single entry, listing the cur-
rently active procedure at the external subprogram level.  The "referencing
environment" of an internal procedure, which includes all the places where
variables (except dummy arguments "passed by reference") might be located,
consists of:
    (1) the activation record for the internal procedure in which the refer-
        ence to the variable appears,
    (2) the activation record for the host procedure,
    (3) static storage, or
    (4) the heap.
Languages that support recursion but do not limit inheritance to one level
must implement a more elaborate display table to accomodate the expansion of
case 2.
 
RESULT Name
 
The heading of a function may specify that the identifier to be used in
defining the value of the function result is different from the function name.
No data attributes are declared for the result name; it assumes all data
attributes of the function name.
 
    A recursive function must be given a result name in order to call itself.
If no result name is given, references to the function name in executable
statements are interpreted not as recursive function calls but as references
to a result variable that has the same name as the function.  (However, a
recursive function without a result name may call itself indirectly.)  When
there is a separate result name, references to the function name in executable
statements (including the left-hand sides of assignment statements) are inter-
preted as recursive function calls.
 
    A nonrecursive function may be given a result name.  The result name,
rather than the function name, must then be used for defining the function
result value (but never for declaring its attributes).  This feature may be
useful in definitions of structure-valued or array-valued functions.
 
Modules
 
A module is a container for data and subprogram declarations that will be
"imported" into other program units by means of a USE statement.
 
    A module has a three-level structure.  The module itself consists of a
specification part followed by a module subprogram part.  (Either part may be
empty.  The module subprogram part, if any, is introduced by a CONTAINS state-
ment.)  The module subprogram part contains subroutine or function subprograms
that may in turn contain internal procedures at the third level.
 
    Although a module subprogram has exactly the same form as an ordinary
(external) subprogram, it must be invoked from another subprogram in the same
module or from an executable program unit that imports it from the module.
Because of the way the Fortran 88 USE operation is defined, an imported module
may be employed just as if the module text were incorporated into the subpro-
gram where the USE statement appears (but without access to names declared
PRIVATE).
 
    Statements in the specification part of a module may have any form that is
permitted in other program units (with a few exceptions).  In particular,
named constant declarations or derived-type structure definitions for global
use may be placed in a module.  Such constants and structures may be imported
into any program unit with a USE statement referring to the module, or they
may be inherited by any module subprogram within the module itself.  Variables
to be shared by the module subprograms may also be declared in the specifica-
tion part of the module.
        MODULE Module_Name
          IMPLICIT NONE
          INTEGER, PRIVATE :: N, R
        CONTAINS
          SUBROUTINE Binomial
            INTEGER Factorial, K
            PRIVATE
            CALL Input_And_Output
          CONTAINS
            SUBROUTINE Input_And_Output
            READ *, N, R
            PRINT *, ' N =', N, ' R =', R, ' C =' &
              , Factorial (N) / (Factorial (R) * Factorial (N - R))
            END SUBROUTINE Input_And_Output
            RECURSIVE INTEGER FUNCTION Factorial (K) RESULT Value
              IF (K <= 1) THEN
                Value = 1
              ELSE
                Value = K * Factorial (K - 1)     ! Recursive call
              END IF
            END FUNCTION Factorial
          END PROGRAM Binomial
        END MODULE Module_Name
 
    The names of data objects, derived-type definitions, and module subpro-
grams may be declared to be PRIVATE: i.e., program units outside the module
are not permitted to import them.  Also, in order to resolve name conflicts a
USE statement may include a RENAME clause designating local identifiers dif-
ferent from the identifiers that appear in the module.
 
    Some important module applications are listed in the Fortran 88 document:
    --  A common block and all of its associated specification statements
        may be imported from a module into all of the program units where
        it is needed.  This may have some efficiency advantage over INCLUDE,
        in that the specifications need to be parsed only once.
    --  Global data may be accessed from a module without using COMMON.  Glo-
        bal constants are also possible:
            MODULE Global_Data
                REAL, PARAMETER :: Pi = 3.141592653589793238462643, &
                 Speed_Of_Light = 2.9979250E8, Avogadro = 6.022169E23
            END MODULE
    --  Data structures: A structure may be defined in a module and accessed
        in a number of program units.  This is the only way to access the
        same structure definition in more than one program unit:
            MODULE Linked_List_Node
              TYPE Information_Part
                CHARACTER (20) Identification
                INTEGER Sequence, Count
              END TYPE Information_Part
              TYPE Node
                TYPE (Information_Part) Information ! Component is a structure
                TYPE (Node), POINTER :: Next
              END TYPE Node
            END MODULE
        A module may contain subprograms that define user-defined operations
        applicable to structures of a derived type defined in the same module.
        The details of the operations may be declared PRIVATE to guarantee
        proper "information-hiding" and encapsulation of the derived type with
        its operations.
    --  Global allocatable arrays: A program may need a large array whose size
        is determined after execution begins (for example, by the value of an
        input variable).  An allocatable array may be declared in a module and
        imported by all of the program units that need it.  The size is deter-
        mined and the array is allocated at the beginning of execution.
 
    When a name is imported from a module via a USE statement, the type and
other attributes must not be specified in the procedure to which it is impor-
ted.  The attributes are those specified in the module.  If an imported name
is changed by a RENAME clause in the USE statement, the original attributes
apply to the new name in the procedure to which it is imported.  Thus the
original name may be used for other purposes within this procedure.  The sym-
bol "=>" (i.e., {local identifier} => {module identifier}) activates the
rename feature.
 
        MODULE Linked_List_Node
          TYPE Information_Part
            CHARACTER (20) Identification
            INTEGER Sequence, Count
          END TYPE Information_Part
          TYPE Node
            TYPE (Information_Part) Information ! Component is a structure
            TYPE (Node), POINTER :: Next
          END TYPE Node
        END MODULE
 
        PROCEDURE Process
          USE Linked_List_Node, Data => Information, Id => Identification
          TYPE (Node) Static_Pointer
          ...
          ALLOCATE (Static_Pointer)
          Static_Pointer % Data % Id = ' George Washington  '
          Static_Pointer % Data % Sequence = 0
          Static_Pointer % Data % Count = Static_Pointer % Data % Count + 1
          NULLIFY (Static_Pointer % Next)
          ...
 
    The point was made earlier, that recursion in Fortran 88 is easier to
implement because name inheritance extends to only one nesting level.  Modules
have an additional level, but implementation remains simple because the outer
level (the module level) is not recursive.  Any variable that belongs to the
entire module (but not to any module procedure) is either on the heap or
static.  Thus it remains true, for procedures and internal procedures inside a
module, that storage for a variable referenced in an internal procedure must
be located in one of four places: in the activation record for the internal
procedure, in the activation record for the host (the module procedure), on
the heap, or in static storage.
 
Explicit interface
 
The program unit from which a procedure is invoked must import or contain an
explicit interface for the procedure in certain cases, for example: if the
procedure result is an array; if any dummy argument is a pointer, a pointer
target, or an assumed-shape array (i.e., one whose shape will be assumed from
the actual argument array); or if the procedure has an optional dummy argument
or is referenced with an argument keyword (except for an intrinsic procedure
reference).
 
    The simplest way to provide an explicit interface, when one is required,
is to define the procedure in a module and import it via a USE statement into
program units that invoke the procedure.
 
    An alternative is to include, in program units from which the procedure is
invoked, an "interface block" consisting essentially of a copy of a portion of
the subprogram in which the procedure was originally defined, namely that por-
tion of the subprogram that specifies the attributes of the dummy arguments
and of the function result (if it is a function).  The names of the dummy arg-
uments in the interface block may be different from those in the original sub-
program, however.
 
    This alternative has the disadvantage, however, that the interface infor-
mation must be copied into each program unit that invokes the procedure.  Cop-
ying may be avoided by placing the interface block in a module, but then this
method has little advantage over defining the entire procedure in a module
unless the complete procedure definition is not readily accessible.  There are
some cases in which the latter situation might occur.  For instance, the
procedure might be in a library for which the source text is not available.
As another example, in a program development environment at a certain stage,
references to a particular unimplemented procedure might appear only in pro-
gram branches whose execution is currently inhibited.
 
Optional and Keyword Arguments
 
Any dummy argument of a procedure may be declared to be optional.  The actual
arguments may include a keyword that matches a dummy argument name in the
explicit interface.  Both of these features are especially useful for calling
a library routine that has a long list of dummy arguments, not all of which
are required at every reference to the routine.
        PROGRAM Invoker
          INTERFACE
            SUBROUTINE Call_Me (First, Second, Third)
              INTEGER, OPTIONAL :: Second
              INTEGER First, Third
          END INTERFACE
          ...
          CALL Call_Me (3, Third = 22)
          ...
        END PROGRAM Invoker
 
    An actual argument that does not have a keyword is associated by position,
in the traditional way.  The positional arguments in an actual argument list
must precede the keyword arguments.
 
    Thus an actual argument list may consist of some positional arguments
(required or optional, but without skipping any positions) followed by a mix-
ture (in any order, and in keyword form) of the remaining required arguments
along with those remaining optional arguments that are needed in this particu-
lar procedure reference.
 
    A procedure with optional dummy arguments may use the PRESENT intrinsic
function to determine whether a particular optional dummy argument actually
appeared in the actual argument list at the current invocation of the proced-
ure.
 
New Intrinsic Procedures
 
Fortran 88 has a large number of intrinsic procedures beyond those of Fortran
77.  Keyword forms are defined for all intrinsic procedure arguments.  Many
intrinsic procedures now have optional arguments;  some old intrinsic
procedures now have additional arguments that are optional:  for example, the
numeric type conversion functions now have an optional KIND argument.
 
    Note the absence of any "matrix divide" operation such as a matrix inverse
or an operation to compute X from A and B where AX = B.
 
    The following is a selection.
 
    Numeric inquiry functions:  These are defined in terms of a "model" number
representation for the processor.  Some functions return information based on
the attributes of the argument, but do not necessarily compute its value.
    --  Digits (X): number of significant (radix) digits in the model;
    --  Epsilon (X): number that is almost negligible compared to one;
    --  Huge (X): value of largest number in the model;
    --  Kind (X): value of the kind (type parameter) attribute;
    --  MaxExponent (X): maximum (radix) exponent in the model;
    --  MinExponent (X): minimum (radix) exponent in the model;
    --  Precision (X): decimal precision;
    --  Radix (X): radix of the model;
    --  Range (X): decimal exponent range;
    --  Selected_Real_Kind (P [, R]): kind type parameter for reals with spec-
        ified decimal exponent range R and decimal precision P;
    --  Tiny (X): value of smallest number in the model.
 
    Array inquiry functions:
    --  Allocated (Array): true if array is currently allocated;
    --  Lbound (Array [, Dim]): lower bound in specified dimension, or vector
        of lower bounds;
    --  Shape (Source): vector containing extents in each dimension;
    --  Size (Array [, Dim]): extent in specified dimension, or total size;
    --  Ubound (Array [, Dim]): upper bound in specified dimension, or vector
        of upper bounds;
 
    Bit operations (including those defined in MIL-STD 1753) on integers:
    --  Bit_Size (I): number of bits for integers in the model;
    --  Btest (I, Pos): true if specified bit position of I contains "1";
    --  IAnd (I, J): bitwise And of I and J;
    --  IBClr (I, Pos): set specified bit position of I to "0";
    --  IBits (I, Pos, Len): extract Len bits from I beginning at Pos;
    --  IBSet (I, Pos): set specified bit position of I to "1";
    --  IEOr (I, J): bitwise Exclusive Or of I and J;
    --  IOr (I, J): bitwise Or of I and J;
    --  IShift (I, Shift [, Size]): end-off left shift [Size rightmost] bits
        of I by Shift positions (right if Shift is negative);
    --  IShiftC (I, Shift [, Size]): circular left shift [Size rightmost] bits
        of I by Shift positions (right if Shift is negative);
    --  MvBits (From, FromPos, Len, To, ToPos): copy Len bits from From to To;
    --  Not (I): bitwise Not of I.
 
    Additional character operations:
    --  AChar (I): ASCII character in ordinal position I;
    --  AdjustL (String): move leading blanks to right end;
    --  AdjustR (String): move trailing blanks to left end;
    --  IAChar (C): ASCII ordinal position of character C;
    --  Len_Trim (String): length of string ignoring trailing blanks;
    --  Repeat (String, NCopies): catenate String with itself NCopies times;
    --  Scan (String, Set [, Back]): position of leftmost character of String
        that is in Set (or rightmost if Back is true), 0 if none in;
    --  Trim (String): initial substring of String, omitting trailing blanks;
    --  Verify (String, Set [, Back]): position of leftmost character of
        String that is not in Set (or rightmost if Back is true), 0 if all in.
 
    Many array operations, including:
    --  CShift (Array, Dim, Shift): circular left shift complete rank-one sec-
        tions of Array along specified dimension (right if Shift is negative);
    --  DotProduct (Vector_A, Vector_B): numerical or logical dot product;
    --  EOShift (Array, Dim, Shift): end-off left shift complete rank-one sec-
        tions of Array along specified dimension (right if Shift is negative);
    --  MatMul (Matrix_A, Matrix_B): numerical or logical matrix product;
    --  MaxLoc (Array [, Mask]): location of a maximum element in Array;
    --  MinLoc (Array [, Mask]): location of a minimum element in Array;
    --  Pack (Array, Mask [, Vector]): create a vector from elements of Array
        selected by Mask; if Vector is present and is longer than the number
        of true positions in Mask, append the remaining elements from Vector;
    --  Product (Array [, Dim] [, Mask]): product of all [selected] elements of
        [along specified dimension];
    --  Sum (Array [, Dim] [, Mask]): sum of all elements of Array [along
        specified dimension];
    --  Reshape (Shape, Source [, Pad] [, Order]): take all elements from
        Source in storage sequence order, combine them into an array expres-
        sion of specified Shape [in subscript order permuted by Order] [, and
        append elements from Pad if necessary];
    --  Transpose (Matrix): transpose matrix of any type;
    --  Unpack (Vector, Mask, Field): form an array expression by placing con-
        secutive elements from Vector into positions where Mask is true, in
        storage sequence order, and copying Field where Mask is false.  Field
        may be a scalar, or an array whose shape is the same as that of Mask.
The Mask argument in MaxLoc, MinLoc, Product, and Sum is a logical array; and
the function is applied to elements where Mask is true.  The Shift argument of
CSHIFT and EOSHIFT may be a scalar or an integer vector whose length is 1 less
than the rank of Array, and whose positive or negative element values specify
the Shift separately for each dimension of Array.
 
    Intrinsic subroutines, including:
    --  Date_And_Time ([All] [, Count] [, MSecond] [, Second] [, Minute]
        [, Hour] [, Day] [, Month] [, Year] [, Zone]);
    --  Random (Harvest): store next pseudorandom number in Harvest.
 
    The subroutine Date_And_Time stores all of the remaining nine values in
the vector All; sets Count to a processor-dependent "system clock count"
value;  sets MSecond (millisecond part), Second, Minute, Hour (0 to 23), Day
(of month), Month, and Year to local time and date; and sets Zone to the
number of minutes that local time is in advance of Coordinated Universal Time.
 
    Random stores the next item (or items, if Harvest is an array) from a
pseudorandom sequence in Harvest.  Another subroutine, RandomSeed, sets or
gets seed values.
 
                      3  CONTROL STRUCTURE ENHANCEMENTS
 
Block-DO
 
Fortran 88 enhances the traditional DO loop construct, but marks as obsoles-
cent certain looping features that have been traditional.  The obsolescent
features that pertain to loops are
    (1) Real and double precision DO variables and DO parameters; and
    (2) Multiple DO loops ending on the same statement, and DO loop termina-
        tion on an action statement (e.g., assignment).
 
    The Fortran 88 DO construct has two alternative DO statement forms, one
with a label after the keyword DO and one without a label in this position.
The labelled form of course includes the traditional DO statement.
 
    If the label after DO is omitted, the final statement of the block DO
construct must be END DO:
        DO I = 1, M
          ...
        END DO
There are several alternative forms for the loop control, and the construct
may have a name, as described below.
 
    If the label is present, the same label must appear at the left of the
final statement of the construct.
            DO 10, I = 1, M
              ...
        10  CONTINUE
            ...
            DO 20, I = 1, M
              ...
        20  END DO
The alternative loop control forms and the construct name also apply to the
labelled version.
 
    A Fortran 77 DO loop (illustrated by the "D0 10" loop above) is classified
as a block-form DO construct with a label after the DO keyword, if its final
statement is a CONTINUE statement that is not shared by more than one DO
block.
 
    If the final statement of a DO loop is shared, or if the final statement
is a statement other than CONTINUE or END DO, the loop is classified as a
nonblock DO construct.  The nonblock form is obsolescent in Fortran 8X.
 
    A "DO construct name", which has the same form as a variable name, may
optionally be used with either the block form or the nonblock form when the
final statement is END DO.  If it appears, this identifier (followed by a
colon) precedes the keyword DO in the DO statement.  (The DO construct name is
not a label.  In fixed source form, it must be begin in coulmn 7 or later.)
The same identifier (without the colon) must be written following END DO on
the final statement of the construct.
 
    An important use of the DO construct name is with the EXIT and CYCLE
statements, especially in a nest of DO blocks.  An EXIT or CYCLE statement
that appears in an inner block may reference the name of an outer block.  Such
a statement will often be part of an IF construct, so that it will be executed
conditionally.  The EXIT or CYCLE statement will cause the inner loop to be
terminated.  An EXIT statement will also cause termination of the named block;
CYCLE terminates the current iteration of the named block and begins the next
iteration (if any).
 
    Fortran 88 provides several forms of loop control:
    (1) With a loop-count control that includes a DO variable and an iteration
        count.  This is the classic Fortran DO.
    (2) DO while a logical expression is true.
    (3) DO forever.
 
    All of these loop control forms are available with the block form DO
construct (with or without a label following the DO keyword, and with or
without a construct name), as well as with the obsolescent nonblock form DO
construct.  For example:
 
        COUNT_CONTROLLED_LOOP: DO, I = 1, M
        ...
 
        WHILE_LOOP: DO, WHILE (ASSOCIATED (POINTER))
        ...
 
        DO_FOREVER: DO
            EXIT IF (IOSTAT < 0)
 
Case
 
The syntax of the Fortran 88 CASE construct is illustrated in the following
example.  The program calls the intrinsic function Date_And_Time, using
keyword arguments Day, Month, and Year.  It then calls the function Julian to
determine the Julian day number, and performs a SELECT CASE operation based on
the Julian day number modulo 7, which indicates the day of the week.  The
identifiers Mon, Tue, etc. denote named constants corresponding to the
different integers that may be produced by the Modulo function.  The CASE
construct sets Alarm_Clock to one of several values depending on the day of
the week.
        PROGRAM Wake_Up
          IMPLICIT NONE
          INTEGER, PARAMETER :: Mon = 0, Tue = 1, Wed = 2, Thu = 3 &
                              , Fri = 4, Sat = 5, Sun = 6
          INTEGER Day_Of_Month, Mo, Yr, Julian_Day_Number
          CALL Date_And_Time (Day = Day_Of_Month, Month = Mo, Year = Yr)
          Julian_Day_Number = Julian (Yr, Mo, Day_Of_Month)
          Clock: SELECT CASE (Modulo (Julian_Day_Number, 7)
            CASE (Sun)
              Alarm_Clock = 1200
            CASE (Mon : Fri)
              Alarm_Clock = 600
            CASE (Sat)
              Alarm_Clock = 800
            CASE DEFAULT
              CALL Error
          END SELECT Clock
          PRINT *, Alarm_Clock
        CONTAINS
          FUNCTION Julian (IYr, Mon, IDay)
            KYr = IYr + 4712
            K1 = 365 * KYr + KYr / 4
            IF (Mon .LT. 3) THEN
                K2 = 31 * (Mon - 1)
                IF (Mod (KYr, 4) .EQ. 0) K2 = K2 - 1
              ELSE
                K2 = Int (30.6 * Mon - 32.3)
              END IF
            Julian = K1 + K2 + Iday
            IF (Julian .GT. 2361221) THEN
                KYr = IYr - 300
                IF (Mon .LT. 3) KYr = KYr - 1
                ICent = KYr / 100
                Julian = Julian - (ICent * 3) / 4 - 1
              END IF
          END FUNCTION Julian
          SUBROUTINE Error
          END SUBROUTINE Error
        END PROGRAM Wake_Up
 
    Notice that the CASE construct has the name Clock.  This identifier may
optionally apear on any of the CASE statements in the construct.
 
    The expression following SELECT CASE is an expression of type integer,
character, or logical.  The case selector in a CASE statement may be a single
expression of the same type, or a pair of expressions separated by a colon
indicating a range of values (except for logical type).  The colon may also
appear with one of the bounding expressions omitted.  In the second CASE
statement of the above example, for instance, the range might have been writ-
ten "(: Fri)" instead of "(Mon : Fri)".  The values designated by selectors in
different CASE statements of a construct must not overlap.
 
                             4  INPUT AND OUTPUT
 
Non-Advancing Input and Output
 
The control list of a formatted input or output statement may include the
specifier "ADVANCE = 'YES'" or "ADVANCE = 'NO'".  The default is 'YES' for
traditional "advancing" or record-oriented input or output, which positions
the file between records after each READ or WRITE.  Non-advancing input or
output, specified by ADVANCE = 'NO', does not change the position of the file
before or after data transfer.  Thus the file may be positioned within a
record after data transfer has occurred, and additional data may be
transferred to or from the same record by a subsequent input or output
statement.
 
Open Specifiers for POSITION, ACTION, DELIM, and PAD
 
Fortran 88 provides some additional specifiers in the OPEN statement:
 
    POSITION = 'REWIND', 'APPEND', or 'ASIS' specifies the positioning of the
file that is to be performed as a result of execution of the OPEN statement.
A new file will be positioned at its initial point.  A file that exists prior
to execution of the OPEN statement will be positioned at its initial point if
the POSITION specifier value is 'REWIND', or at its terminal point (or just
prior to the endfile record, if any) if the value is 'APPEND'.  An OPEN state-
ment specifying POSITION = 'ASIS' does not reposition the file.  The default,
equivalent to Fortran 77, is 'ASIS'.
 
    ACTION = 'READ', 'WRITE', or 'READWRITE' specifies which kinds of data
transfer statements are permitted.  The default, equivalent to Fortran 77, is
'READWRITE'.  WRITE, PRINT, and ENDFILE statements are permitted only if
ACTION is 'WRITE' or 'READWRITE';  READ statements are permitted only if
ACTION is 'READ' or 'READWRITE'.
 
    DELIM = 'APOSTROPHE', 'QUOTE', or 'NONE' specifies the delimiter to be
used for character strings written with list-directed or NAMELIST formatting.
The default, equivalent to Fortran 77, is 'NONE'.  This specifier is permitted
in an OPEN statement only if the form for the connection is FORMATTED.
 
    PAD = 'YES' or 'NO' specifies whether or not the required record length,
based on the input list and the format specification, is permitted to exceed
the actual record length.  The default is 'YES': this is an extension to For-
tran 77 which prohibits a required record length greater than the actual rec-
ord length.  If PAD is 'YES', formatted input proceeds as if the actual record
were at least as long as required, with trailing blanks supplied if necessary.
 
Input Data Count
 
Fortran 88 provides count value specifiers, giving the number of characters
from the actual input record that were processed during execution of a
nonadvancing input statement (excluding trailing blanks supplied when PAD is
'YES'), or the number of null input data items that were encountered during
execution of a list-directed or namelist input statement.  (Null data items,
as in Fortran 77 list-directed input, appear in the input file as a pair of
consecutive separators with no data between them, no data preceding the first
separator encountered by an input statement, or a repeat count with no data
following.)  These counts become defined at the end of execution of an input
statement with a control list containing the specifier "SIZE = {integer var-
iable}" or "NULLS = {integer variable}", respectively.
 
Namelist
 
The control list of a READ, WRITE, or PRINT statement may contain a "namelist
group name" (optionally preceded by "NML =") instead of a format specifier.
Such a statement does not have an input or output list.
 
    The namelist group name must be declared, imported, or inherited by any
procedure that uses it in an input or output statement.  A NAMELIST declara-
tion is:
        NAMELIST / {namelist group name} / {variable name list}
The variables named in the list may include structures, arrays, and array
sections.
 
    Data for namelist input begins with "&" followed by the namelist group
name (which must match the group name in the input control list).  This is
then followed by a sequence of name-value pairs, ending with a slash.  The
name in each pair must be one of the variable names listed in the NAMELIST
declaration.  An "=" separates the name in each pair from the value.  The
value in each pair is a single input data item, except that when the named
variable is a structure, an array, or an array section the value may consist
of a set of data items.  The data items are separated in the same way as
list-directed input items, and may include null items and repeat counts.
 
    Namelist output appears on the external file in the same way as list-
directed output, except that "&" followed by the namelist group name will
appear at the beginning of the first record written, and each name in the var-
iable name list of the NAMELIST statement appears in order followed by "=" and
then by its value (which is a single data item, or a set of items for a struc-
ture, an array, or an array section).
 
Input and Output of Whole Arrays and Structures
 
An input or output list may specify an array name denoting input or output of
the whole array as in Fortran 77.  An array section may also be specified.
The name of a structure may be specified to denote input or output of the
whole structure, provided that the structure does not have any pointers as
"ultimate" components: i.e., the components that result from recursively
decomposing any components that are arrays or structures.  For formatted input
or output, a separate edit descriptor is required for each element of an array
or array section that is named in the input or output list, and for each
ultimate components of a structure that is named.
 
New Edit Descriptors
 
Fortran 88 permits a G edit descriptor for data of integer, character, or
logical type, as well as real (permitted by Fortran 77).
 
    B, O, and Z edit descriptors correspond to list items of integer type and
to external data items in binary, octal, and hexidecimal form.
 
    The EN edit descriptor for real output produces a data item similar to
that produced by the E edit descriptor, except that the decimal exponent is
constrained to be a multiple of 3, and the significant part is between 1 and
1000 (except when the data value is zero).  EN is the same as E for real
input.
 
 
 
)
Keith H. Bierman      |*My thoughts are my own. Only my work belongs to Sun*
It's Not My Fault     |	Marketing Technical Specialist    ! kbierman@sun.com
I Voted for Bill &    |   Languages and Performance Tools. 
Opus  (* strange as it may seem, I do more engineering now     *)

chidsey@smoke.BRL.MIL (Irving Chidsey ) (06/14/89)

So many new ways I can screw up!

In the future could the make medium sized changes every five years?
Instead of a new language every 10 to 15 years?
I am getting to old to learn all that before I retire.

				Irv
-- 
I do not have signature authority.  I am not authorized to sign anything.
I am not authorized to commit the BRL, the DOA, the DOD, or the US Government
to anything, not even by implication.
			Irving L. Chidsey  <chidsey@brl.mil>

jhol@tolsun.oulu.fi (Jouko Holopainen) (06/20/89)

In article <10398@smoke.BRL.MIL> chidsey@brl.arpa (Irving Chidsey (INF) <chidsey>) writes:

>I am getting to old to learn all that before I retire.

Nothing personal, just that 100% of code I have ever seen published on
any book/paper contains 0% f77 and 100% f66. That is, no IF/THEN/ELSE/ENDIF
but rather IF() 10 20 30 ...

Most annoying to see "conversion to other languages is easy" or "maximum
readability" and then constructs like IF () GOTO 30 ... 30 CONTINUE

I would have liked to see arithmetic IF removed from f88...

>				Irv
--
Jouko Holopainen : jhol@tolsun.oulu.fi

Hi. I'm not home right now. But if you want to leave a message, just start
talking at the sound of the tone.

khb@chiba.Sun.COM (Keith Bierman - SPD Languages Marketing -- MTS) (06/20/89)

In article <666@tolsun.tut.fi> jhol@tolsun.UUCP (Jouko Holopainen) writes:
>In article <10398@smoke.BRL.MIL> chidsey@brl.arpa (Irving Chidsey (INF) <chidsey>) writes:
>
>>I am getting to old to learn all that before I retire.
>
>Nothing personal, just that 100% of code I have ever seen published on
>any book/paper contains 0% f77 and 100% f66. That is, no IF/THEN/ELSE/ENDIF
>but rather IF() 10 20 30 ...

I suggest that you have not looked very hard. I went over to my handy
bookcase and pulled the FIRST non-manual likely to include code ...
page 526 of Numerical Recipes  ..

	IF (IHIT .EQ. 0) THEN
	   LISTA(KK) = J
	   KK        = KK+1
	ELSE IF (IHIT .GT. 1)  .... ETC

SECOND BOOK


PAGE 521 of "solving problems on concurrent processors"

	IF (TASK .NE. QUIT) THEN
	   IF (TASK .EQ.UPDATE) THEN
		CALL INITCP
	   ELSEIF (TASK .EQ. UPDATE) ... ETC.

I do own books which use older notation (e.g. my old CDC and UNIVAC
manuals, Metcalfs old book on Optimization) but many books have "upgraded"
	
>
>Most annoying to see "conversion to other languages is easy" or "maximum
>readability" and then constructs like IF () GOTO 30 ... 30 CONTINUE
>
>I would have liked to see arithmetic IF removed from f88...

If all your books are still f66 ... what about your programs ? Would
you really want them all to break ? What one hopes to have happen is
for the obsolete forms (viz. if () 1,2,3) to slowly wither away.
Sudden removeal would reduce the utility of the standard.
Keith H. Bierman      |*My thoughts are my own. Only my work belongs to Sun*
It's Not My Fault     |	Marketing Technical Specialist    ! kbierman@sun.com
I Voted for Bill &    |   Languages and Performance Tools. 
Opus  (* strange as it may seem, I do more engineering now     *)