VMS Help
FORTRAN, Statements

 *Conan The Librarian (sorry for the slow response - running on an old VAX)

  Statements in a Fortran program unit follow a required order.  In
  the following figure, vertical lines separate statement types that
  can be interspersed.  For example, DATA statements can be
  interspersed with executable statements.  Horizontal lines indicate
  statement types that cannot be interspersed.  For example, type
  declaration statements cannot be interspersed with executable
  statements.

  +-------+--------------------------------------------------------+
  |       |              OPTIONS Statement                         |
  |       |--------------------------------------------------------|
  |       |PROGRAM, FUNCTION, SUBROUTINE, or BLOCK DATA Statements |
  |       |--------+-----------------------------------------------|
  |COMMENT|         |  IMPLICIT NONE Statement                     |
  | Lines,|         |-------------------------------+--------------|
  |INCLUDE|NAMELIST,|  IMPLICIT Statements          |              |
  | State-| FORMAT, |------+------------------------|  PARAMETER   |
  | ments,|   &     |      |  Other Specification   |  Statements  |
  |& Gen- | ENTRY   | DATA |      Statements,       |              |
  |  eral | State-  |State-|  DICTIONARY Statements |              |
  |Direc- |  ments  | ments|------------------------+--------------|
  | tives |         |      |   Statement Function Definitions      |
  |       |         |      |---------------------------------------|
  |       |         |      |       Executable Statements           |
  |-------+---------+------+---------------------------------------|
  |                     END Statement                              |
  +----------------------------------------------------------------+

  1 - Directive Statements

  CDEC$ ALIAS name, external-name
  CDEC$ ASSERT (e)
  CDEC$ END OPTIONS (see CDEC$ OPTIONS)
  CDEC$ IDENT string
  CDEC$ INIT_DEP_FWD
  CDEC$ NOVECTOR
  CDEC$ OPTIONS /qual...
  CDEC$ PSECT /common-name/ attr [,attr,...]
  CDEC$ SUBTITLE string
  CDEC$ TITLE string

  CPAR$ CONTEXT_SHARED var_name[,...,var_name]
  CPAR$ CONTEXT_SHARED_ALL
  CPAR$ DO_PARALLEL [distribution-size]
  CPAR$ LOCKON lock-variable
  CPAR$ LOCKOFF lock-variable
  CPAR$ PRIVATE name[,...,name]
  CPAR$ PRIVATE_ALL
  CPAR$ SHARED common_name[,...,common_name]
  CPAR$ SHARED_ALL

  You can use directives in a Fortran source program to influence
  certain aspects of the compilation process.

  Directives are prefixed, starting in column 1, with a 5-character
  identifier and a space (or tab).  Directives prefixed with CDEC$
  are enabled in all Fortran compilation units, regardless of the
  qualifiers used on the FORTRAN command line.

  Directives may also be prefixed with a first character of ! (!DEC$
  or !PAR$) in any column of a source line as long as only whitespace
  (blanks or tabs) precedes the directive prefix.

  Directives prefixed with CPAR$ are enabled only in Fortran
  compilation units involved in parallel processing (that is, when
  the /PARALLEL qualifier is specified on the FORTRAN command line).
  If the /PARALLEL qualifier is not specified, parallel-processing
  directives (CPAR$ directives) are interpreted as comment lines.

  A directive statement cannot be continued across multiple lines in
  a source program, and any blanks appearing after column 6 are
  insignificant.

  Continuation lines cannot appear in directive statements.

  If a blank common block is used in a compiler directive, it must be
  specified as two slashes (/ /).

 1.1 - ALIAS

  CDEC$ ALIAS name, external-name

  The ALIAS directive lets you specify an alternate external name to
  be used when referring to external objects such as subroutines and
  functions.  This can be useful when compiling applications written
  for other platforms which have different naming conventions.

  The external-name may be an identifier or a quoted character constant.
  If a quoted character constant is specified, it is used as-is; the
  string is not changed to upper case nor are blanks removed.  Names
  which are not acceptable to the OpenVMS linker will cause link-time
  errors.

  The ALIAS directive affects only the external name used for references
  to the specified internal name.

 1.2 - ASSERT

  CDEC$ ASSERT (log-exp)

  or in statement form:

  ASSERT (log-exp)

  log-exp  Is a logical expression.

  The ASSERT directive (also available in statement form) provides
  the compiler with information to improve optimization (particularly
  if vectorization or automatic decomposition for parallel processing
  is being performed).  The directive can also be used to provide a
  form of error checking in user applications.

  The ASSERT directive tells the compiler that "log-exp" evaluates as
  .TRUE.  at the location in the program unit where the ASSERT
  appears.

  If the compiler option /CHECK=ASSERTIONS (or
  OPTIONS/CHECK=ASSERTIONS) is in effect, the compiler adds run-time
  code to verify the asserted expression; if the expression evaluates
  as .FALSE., a run-time error is signaled.

  The following is an example of how to use the CDEC$ ASSERT
  directive for error checking (the program is compiled using the
  compiler option /CHECK=ASSERTIONS:

  CDEC$ ASSERT (ICOUNT .NE. 0)
        IVAL = IVAL / ICOUNT      ! Avoid zero-divide exception

 1.3 - IDENT

  CDEC$ IDENT string

  The IDENT directive lets you specify a string that can be used to
  identify an object module.  The compiler places the string in the
  identification field of an object module when it generates the
  module for each source program unit.  The string that you specify
  can consist of a group of up to 31 printable characters delimited
  by apostrophes.

  Only the first IDENT directive is effective -- the compiler ignores
  any additional IDENT directives in a program unit.

 1.4 - INIT_DEP_FWD

  CDEC$ INIT_DEP_FWD

  The INIT_DEP_FWD (INITialize DEPendences ForWarD) directive
  specifies that the compiler is to begin its dependence analysis by
  assuming all dependences occur in the same forward direction as
  their appearance in the normal scalar execution order.  This
  contrasts with the normal compiler behavior, which is for the
  dependence analysis to make no initial assumptions about the
  direction of a dependence.

  The INIT_DEP_FWD directive must precede the DO statement for each
  DO loop.  No source code lines, other than the following, can be
  placed between the INIT_DEP_FWD directive statement and the DO
  statement:  an optional CPAR$ DO_PARALLEL directive, a CDEC$
  NOVECTOR directive, placeholder lines, comment lines, or blank
  lines.

 1.5 - NOVECTOR

  CDEC$ NOVECTOR

  The CDEC$ NOVECTOR directive tells the compiler not to vectorize
  the DO loop following the directive.  This is useful in cases where
  the vectorized form would not perform as well as the scalar form.
  This directive is only available on VAX processors.

  The NOVECTOR directive must precede the DO statement for each DO
  loop to which you want the directive to apply.  No source code
  lines, other than the following can be placed between the NOVECTOR
  directive statement and the DO statement:  an optional CPAR$
  DO_PARALLEL directive, a CDEC$ INIT_DEP_FWD directive, placeholder
  lines, comment lines, or blank lines.

 1.6 - OPTIONS and ENDOPTIONS

  CDEC$ OPTIONS

  The OPTIONS directive controls whether the Compaq Fortran compiler
  naturally aligns fields in records and data items in common blocks
  for performance reasons, or whether the compiler packs those fields
  and data items together on arbitrary byte boundaries.  The OPTIONS
  directive takes the following form:

  CDEC$ OPTIONS /[NO]ALIGN[=p] /[NO]WARNINGS=[NO]ALIGNMENT
         .
         .
         .
  CDEC$ END OPTIONS

  p  Is a specifier with one of the following forms:

     [class =] rule
     (class = rule,...)
     ALL
     NONE

     class  Is one of the following keywords:

            COMMONS    (for common blocks)
            RECORDS    (for records)
            STRUCTURES (a synonym for RECORDS)

     rule   Is one of the following keywords:

            PACKED -   Packs fields in records or data
                       items in common blocks on arbitrary
                       byte boundaries.

            NATURAL -  Naturally aligns fields in records
                       and data items in common blocks on
                       up to 64-bit boundaries (inconsistent
                       with the FORTRAN-77 standard).

                       If you specify NATURAL, the compiler will
                       naturally align all data in a common
                       block, including REAL*8, and
                       all COMPLEX data.

            STANDARD - Naturally aligns data items in common
                       blocks on up to 32-bit boundaries (con-
                       sistent with the FORTRAN-77 standard).

                       Note that this keyword only applies to
                       common blocks; therefore, you can specify
                       /ALIGN=COMMONS=STANDARD, but you cannot
                       specify /ALIGN=STANDARD.

     ALL    Is the same as /ALIGN, /ALIGN=NATURAL, and
            /ALIGN=(RECORDS=NATURAL,COMMONS=NATURAL).

     NONE   Is the same as /NOALIGN, /ALIGN=PACKED, and
            /ALIGN=(RECORDS=PACKED,COMMONS=PACKED)

  CDEC$ OPTIONS (and accompanying CDEC$ END OPTIONS) directives must
  come after OPTIONS, SUBROUTINE, FUNCTION, and BLOCK DATA statements
  (if any) in the program unit, and before statement functions or the
  executable part of the program unit.

  For performance reasons, Compaq Fortran always aligns local data items
  on natural boundaries.  However, EQUIVALENCE, COMMON, RECORD, and
  STRUCTURE data declaration statements can force misaligned data.
  You can use the OPTIONS directive to control the alignment of
  fields associated with COMMON and RECORD statements.  By default,
  you do not receive compiler messages when misaligned data is
  encountered.

  To request aligned data in a record structure, specify
  /ALIGN=RECORDS=NATURAL, or consider placing source data declarations
  for the record so that the data is naturally aligned.

                                 NOTE

          Misaligned data significantly increases the time it
          takes  to  execute  a  program.   As  the number of
          misaligned fields encountered  increases,  so  does
          the  time  needed  to  complete  program execution.
          Specifying  CDEC$  OPTIONS/ALIGN  (or  the   /ALIGN
          compiler option) minimizes misaligned data.

  To request aligned, data in common blocks, specify
  /ALIGN=COMMONS=STANDARD (for data items up to 32 bits in length) or
  /ALIGN=COMMONS=NATURAL (for data items up to 64 bits in length), or
  place source data declarations within the common block in
  descending size order, so that each data field is naturally
  aligned.

  The OPTIONS directive supersedes the /ALIGN compiler option.

  OPTIONS directives must be balanced and can be nested up to 100
  levels, for example:

     CDEC$ OPTIONS /ALIGN=PACKED         ! Group A
        declarations
     CDEC$ OPTIONS /ALIGN=RECO=NATU         ! Group B
        more declarations
     CDEC$ END OPTIONS                      ! End of Group B
        still more declarations
     CDEC$ END OPTIONS                   ! End of Group A

  Note that common blocks within Group B will be PACKED.  The CDEC$
  OPTION specification for Group B only applies to RECORDS, so
  COMMONS retains the previous setting (in this case, from the Group
  A specification).

  For more information on alignment and data sizes, see your user
  manual.

  The /WARNINGS qualifier may be specified to control whether or not
  alignment warnings are given for STRUCTURE and COMMON declarations
  within the scope of this CDEC$ OPTIONS directive.  Warnings are given
  only if /WARNINGS=ALIGNMENT was also specified on the command line;
  use the directive qualifier to disable alignment warnings for selected
  declarations.

  For COMMON blocks, all declarations and directives naming the COMMON
  block must have the same setting for /WARNINGS=ALIGNMENT.  For example:

     CDEC$ OPTIONS /WARN=ALIGNMENT
           COMMON /CMN/ X
     CDEC$ END OPTIONS
     CDEC$ OPTIONS /WARN=NOALIGNMENT
           SAVE /CMN/
     CDEC$ END OPTIONS

  will result in a warning message from the compiler.  The initial state
  is taken from the value of /WARNINGS=ALIGNMENT on the command line.

 1.7 - PSECT

  CDEC$ PSECT /common-name/ attr [,attr,...]

  The PSECT directive lets you modify several attributes of a common
  block.

  You specify the name of a common block, preceded and followed by a
  slash, and one of the following attributes:
    LCL         Local scope.
    GBL         Global scope.
    [NO]WRT     Writability or no-writability.
    [NO]SHR     Shareability or no-shareability.
    [NO]MULTILANGUAGE  Length padded to multiple of alignment or not
    ALIGN=val   Alignment for the common block.
                Val must be a constant (0 through 9).

  Refer to the "OpenVMS Linker Reference Manual" for detailed information
  about default attributes of common blocks.

 1.8 - TITLE and SUBTITLE

  CDEC$ TITLE string
  CDEC$ SUBTITLE string

  The TITLE directive lets you specify a string and place it in the
  title field of a listing header.  Similarly, SUBTITLE lets you
  place a specified string in the subtitle field of a listing header.

  The string that you specify can consist of up to 31 printable
  characters and must be delimited by apostrophes.

  In addition to the compiler-directive syntax rules, the TITLE and
  SUBTITLE directives have the following specific rules:

   o  To enable TITLE and SUBTITLE directives, you must specify the
      /LIST compiler option.

   o  When TITLE or SUBTITLE appears on a page of a listing file, the
      specified string appears in the listing header of the following
      page.

   o  If two or more of either directive appear on a page, the last
      directive is the one in effect for the following page.

   o  If either directive does not specify a string, no change occurs
      in the listing file header.

 1.9 - CONTEXT_SHARED

  CPAR$ CONTEXT_SHARED var_name[,...,var_name]
  CPAR$ CONTEXT_SHARED_ALL

  CONTEXT_SHARED directives can be interspersed with declaration
  statements within program units in a parallel-processing
  application program.  Variables (scalars, arrays, and records)
  specified on a CONTEXT_SHARED directive reside in a shared memory
  location throughout any one invocation of a subprogram (subroutine
  or function), including any parallel loops contained within the
  subprogram.

  However, if a subprogram has several concurrent invocations
  (because it is called from within a parallel loop), each invocation
  will use different memory for these variables.  This context
  adjustment is handled automatically by the compiler and is not a
  programming consideration.

  By default, all variables in a routine compiled with the /PARALLEL
  qualifier are context-shared.

  Commas are required between variable names specified on a
  CONTEXT_SHARED directive.

  The CONTEXT_SHARED_ALL directive forces all symbols that are
  declared within a routine to default to CONTEXT_SHARED.  This
  directive affects only default behavior.  Individual symbols can
  still be declared PRIVATE.

  See your user manual for information about when to use directives
  to resolve certain types of data dependence problems.

 1.10 - DO_PARALLEL

  CPAR$ DO_PARALLEL [distribution-size]

  The DO_PARALLEL compiler directive statement identifies an indexed
  DO loop that is to be executed in parallel.

  The DO_PARALLEL directive must precede the DO statement for each
  parallel DO loop.  No source code lines, other than the following
  can be placed between the DO_PARALLEL directive statement and the
  DO statement:  a CDEC$ INIT_DEP_FWD directive, a CDEC$ NOVECTOR
  directive, placeholder lines, comment lines, or blank lines.

  You can specify how the DO loop iterations are to be divided up
  among the processors executing the parallel DO loop.  For example,
  if a parallel DO loop has 100 iterations and you specify a
  distribution size of 25, iterations will be distributed to each
  processor for execution in sets of 25.  When a process completes
  one set of iterations, it then begins processing the next
  unprocessed set.  If the number that you specify for distribution
  size does not divide evenly into the number of iterations, any
  remaining iterations are run in the last process.

  The expression that you use to specify the distribution size must
  be capable of being evaluated as a positive, nonzero integer.  If
  necessary, it is converted to an integer.  For example, 5.2 is
  acceptable and is converted to 5.  The number 0.2 is not
  acceptable, however, because it is converted to 0.

 1.11 - LOCKON and LOCKOFF

  CPAR$ LOCKON lock-variable
  CPAR$ LOCKOFF lock-variable

  The LOCKON and LOCKOFF compiler directive statements can be used
  within a parallel DO loop to prevent multiple processes from
  executing selected statements in parallel.  These directives force
  the multiple processes executing a parallel DO loop to execute
  selected statements serially.  This can be useful when a statement
  (or set of statements) creates an unacceptable data dependence
  problem that cannot be resolved by other means.

  The lock variable can be a variable or a dummy argument.  It must
  have a data type of LOGICAL*4 and must have a status of shared
  (SHARED directive).  The lock is in effect when the lock variable
  has a value of .TRUE.  and unlocked when the lock variable has a
  value of .FALSE.

  The LOCKON and LOCKOFF directives perform the following operations:

    LOCKON     Waits, if necessary, for the lock variable to become
               .FALSE., then sets it to .TRUE. (that is, locks the
               lock), and then proceeds.
    LOCKOFF    Sets the lock variable to .FALSE. (that is, unlocks
               the lock).

  These directives use the VAX interlocked instructions to guarantee
  proper synchronization on a multiprocessor.  Do not use any other
  statements to modify the lock variable while another process may be
  executing a LOCKON or LOCKOFF directive.

  See your user manual for examples of how locks are used in parallel
  DO loops.

 1.12 - PRIVATE

  CPAR$ PRIVATE name[,...,name]
  CPAR$ PRIVATE_ALL

  PRIVATE directives can be interspersed with declaration statements
  within program units in a parallel-processing application program.
  The PRIVATE[_ALL] directive specifies those variables (scalars,
  arrays, and records) and common blocks that must have unique memory
  locations within each of the processes executing a parallel DO
  loop.

  PRIVATE_ALL causes all variables and common blocks declared in a
  routine to default to private -- unless they are explicitly
  declared as shared (for common blocks) or context-shared (for
  variables).  PRIVATE_ALL does not disallow the use of the SHARED
  and CONTEXT_SHARED directives; it merely establishes the default
  behavior for data sharing as PRIVATE, overriding the default
  behavior (SHARED_ALL and CONTEXT_SHARED) established by the
  /PARALLEL qualifier.

  Commas are required between the names that you specify on PRIVATE
  directives.  In addition, common block names must be enclosed by
  slashes (for example, /name/ or, for blank common, / /).

  See your user manual for information about when to use directives
  to resolve certain types of data dependence problems.

 1.13 - SHARED

  CPAR$ SHARED common_name[,...,common_name]
  CPAR$ SHARED_ALL

  SHARED directives can be interspersed with declaration statements
  within program units in a parallel-processing application program.
  The SHARED[_ALL] directive identifies those variables (scalar,
  array, and record variables) and common blocks that are to be
  shared among all the processes executing the compilation unit -- in
  both parallel and nonparallel (serial) execution contexts.

  SHARED_ALL does not disallow the use of the PRIVATE directive; it
  merely reinforces the default behavior for data sharing established
  by /PARALLEL.  The default behavior associated with the /PARALLEL
  qualifier is to give a status of shared to all common blocks
  declared in a given compilation unit.

  Note that any given common block should have the same status
  (shared or private) in all subprograms in the parallel application.
  The common block names must be enclosed by slashes (for example,
  /name/ or, for blank common, / /).  Commas are required between
  names.

  See your user manual for information about when to use directives
  to resolve certain types of data dependence problems.

  2 - Executable Statements

  The executable statements are:

  ACCEPT, ASSIGN, assignment statements, BACKSPACE, CALL, CLOSE,
  CONTINUE, DELETE, DO, END DO, ELSE, END, ENDFILE, FIND, GO TO, IF,
  END IF, INQUIRE, OPEN, PAUSE, PRINT, READ, RETURN, REWIND, REWRITE,
  STOP, TYPE, UNLOCK, and WRITE.

  3 - Specification Statements

  The specification statements are:

  AUTOMATIC, BLOCK DATA, COMMON, DATA, DIMENSION, EQUIVALENCE,
  EXTERNAL, IMPLICIT, INTRINSIC, NAMELIST, PARAMETER, POINTER,
  PROGRAM, RECORD, SAVE, STATIC, structure declarations, type
  declarations, and VOLATILE.

  4 - ACCEPT

    Formatted           ACCEPT f[,iolist]
    List-directed       ACCEPT *[,iolist]
    Namelist            ACCEPT n

      f       Is a format specifier not prefaced by FMT=.

      iolist  Is a simple I/O list element or an implied-DO list.

      *       Specifies list-directed formatting (can be specified
              as FMT=*).

      n       The nonkeyword form of a namelist specifier.

  The control-list parameters are "f," "*" (or FMT=*), and "n".  The
  I/O list parameter is "iolist".

  The formatted ACCEPT statement transfers data from your terminal to
  internal storage.  The access mode is sequential.

  The list-directed ACCEPT statement translates the data from
  character to binary format according to the data types of the
  variables in the I/O list.

  The namelist ACCEPT statement translates the data from character to
  binary format according to the data types of the list entities in
  the corresponding NAMELIST statement.

  Also see the READ Statement.

  5 - ASSERT

  See CDEC$ ASSERT under Statements Directive_Statements in this Help
  file.

  6 - ASSIGN

  Assigns the value of a statement label to an integer variable.
  Statement format:

     ASSIGN s TO v

     s  Is the label of an executable statement or a
        FORMAT statement.  You must specify the label
        as an unsigned integer (from 1-5 characters
        long, using digits 0-9).

     v  Is an integer variable name (must be INTEGER*4).

  When the value of a statement label is assigned to an integer
  variable:  the variable can then be used as a transfer destination
  in a following assigned GOTO statement or as a format specifier in
  a formatted I/O statement.  The ASSIGN statement must be in the
  same program unit as and must be executed before the statement(s)
  in which the assigned variable is used.

  7 - Assignment

  Assigns the value of the expression to the variable.
  Arithmetic/Logical/Character assignment takes the form:

     v = e

     v  Is a scalar memory reference.

     e  Is an arithmetic expression (arithmetic assignment),
        a character scalar memory reference (character assignment),
        or a logical scalar memory reference (logical assignment).

  The right side of the equation must evaluate to a data type
  compatible with the variable on the left side.  If aggregates are
  involved, the aggregate reference and the aggregate must have
  matching structures.

 7.1 - Conversion Rules

  The following tables summarize the conversion rules for assignment
  statements.  MS signifies the most significant (high-order) bit; LS
  signifies the least significant (low-order) bit.

  ----------------------------------------------------------------
  |Variable |          Expression (E)                            |
  |or Array |-----------------------------------------------------
  |Element  |integer or logical |      REAL     |    REAL*8      |
  ----------------------------------------------------------------
  | integer |  Assign E to V    | Truncate E to | Truncate E to  |
  |  or     |                   | integer and   | integer and    |
  | logical |                   | assign to V   | assign to V    |
  ----------------------------------------------------------------
  |  REAL   | Append fraction   | Assign E to V | Assign MS por- |
  |         | (.0) to E and     |               | tion of E to V;|
  |         | assign to V       |               | LS portion of E|
  |         |                   |               | is rounded     |
  ----------------------------------------------------------------
  |  REAL*8 | Append fraction   | Assign E to MS| Assign E to V  |
  |         | (.0) to E and     | portion of V; |                |
  |         | assign to V       | LS portion of |                |
  |         |                   | V is 0        |                |
  ----------------------------------------------------------------
  | REAL*16 | same as above     | same as above | Assign E to MS |
  |         |                   |               | portion of V;  |
  |         |                   |               | LS portion of V|
  |         |                   |               | is 0           |
  ----------------------------------------------------------------
  | COMPLEX | Append fraction   | Assign E to   | Assign MS por- |
  |         | (.0) to E and     | real part of  | tion of E to   |
  |         | assign to real    | V; imaginary  | real part of V;|
  |         | part of V; imagin-| part of V is  | LS portion of  |
  |         | ary part of V is  | 0.0           | E is rounded;  |
  |         | 0.0               |               | imaginary part |
  |         |                   |               | of V is 0.0    |
  ----------------------------------------------------------------
  |COMPLEX*16| Append fraction  | Assign E to MS | Assign E to   |
  |          | (.0) to E and    | portion of     | real part of  |
  |          | assign to V;     | real part of V;| V; imaginary  |
  |          | imaginary part of| imaginary part | part is 0.0   |
  |          | V is 0.0         | of V is 0.0    |               |
  ----------------------------------------------------------------

  continued chart
  ----------------------------------------------------------------
  |Variable |          Expression (E)                            |
  |or Array |-----------------------------------------------------
  |Element  |   REAL*16   |    COMPLEX    |    COMPLEX*16        |
  ----------------------------------------------------------------
  | integer | Truncate E  | Truncate real | Truncate real part of|
  | or      | to integer  | part of E to  | E to integer and     |
  |logical  | and assign  | integer and   | assign to V; imagin- |
  |         | to V        | assign to V;  | ary part of E is not |
  |         |             | imaginary part| used                 |
  |         |             | is not used   |                      |
  ----------------------------------------------------------------
  |  REAL   | Assign MS   | Assign real   | Assign MS portion of |
  |         | portion of E| part of E to  | the real part of E to|
  |         | to V; LS    | V; imaginary  | V; LS portion of the |
  |         | portion of E| part of E is  | real part of E is    |
  |         | is rounded  | not used      | rounded; imaginary   |
  |         |             |               | part of E is not used|
  ----------------------------------------------------------------
  | REAL*8  | same as     | Assign real   | Assign real part of E|
  |         | above       | part of E to  | to V; imaginary part |
  |         |             | MS of V; LS   | of E is not used     |
  |         |             | portion of V  |                      |
  |         |             | is 0; imagin- |                      |
  |         |             | ary part of E |                      |
  |         |             | is not used   |                      |
  ----------------------------------------------------------------
  | REAL*16 | Assign E to | same as above | Assign real part of E|
  |         | V           |               | to MS portion of V;  |
  |         |             |               | LS portion of real   |
  |         |             |               | part of V is 0; imag-|
  |         |             |               | inary part of E is   |
  |         |             |               | not used             |
  ----------------------------------------------------------------
  | COMPLEX | Assign MS   | Assign E to V | Assign MS portion of |
  |         | portion of E|               | real part of E to    |
  |         | to real part|               | real part of V; LS   |
  |         | of V; LS    |               | portion of real part |
  |         | portion of E|               | of E is rounded.     |
  |         | is rounded; |               | Assign MS portion of |
  |         | imaginary   |               | imaginary part of E  |
  |         | part of V is|               | to imaginary part of |
  |         | 0.0         |               | V; LS portion of     |
  |         |             |               | imaginary part of E  |
  |         |             |               | is rounded           |
  ----------------------------------------------------------------
  |COMPLEX*16| same as    | Assign real    | Assign E to V       |
  |          | above      | part of E to   |                     |
  |          |            | MS portion of  |                     |
  |          |            | real part of V;|                     |
  |          |            | LS portion of  |                     |
  |          |            | real part is 0.|                     |
  |          |            | Assign imagin- |                     |
  |          |            | ary part of E  |                     |
  |          |            | to MS portion  |                     |
  |          |            | of imaginary   |                     |
  |          |            | part of V;     |                     |
  |          |            | LS portion of  |                     |
  |          |            | imaginary part |                     |
  |          |            | is 0           |                     |
  ----------------------------------------------------------------

  8 - AUTOMATIC and STATIC

  The AUTOMATIC and STATIC statements are used within a called
  subprogram to control the allocation of storage to variables and
  the initial value of variables.  Statement format:

     AUTOMATIC  v [,v]...
     STATIC  v [,v]...

     v  Is the name of a variable, array, or array declarator.

  The following table summarizes the difference between automatic and
  static variables upon entry to and exit from a subprogram:

  +-----------+---------------------------+------------------------+
  | Variable  | Entry                     | Exit                   |
  +-----------+---------------------------+------------------------+
  | AUTOMATIC | Variables are unassigned, | The storage area allo- |
  |           | and do not reflect any    | cated to the variable  |
  |           | changes caused in the     | is deleted.            |
  |           | previous execution of     |                        |
  |           | the program.              |                        |
  +-----------+---------------------------+------------------------+
  | STATIC    | Values of the subprogram  | The current values of  |
  |           | variables are unchanged   | the variables are kept |
  |           | since the last execution  | in the static storage  |
  |           | of the subprogram.        | area.                  |
  +-----------+---------------------------+------------------------+

  By default, all variables are STATIC.  To change the default from
  STATIC to AUTOMATIC, specify the /RECURSIVE compiler option.

  To override the compiler option in effect for specific variables,
  specify the variables in AUTOMATIC or STATIC type statements.

                                 NOTE

          Variables in COMMON, DATA,  EQUIVALENCE,  and  SAVE
          statements, or in BLOCK DATA subprograms are always
          STATIC,  regardless  of  the  /RECURSIVE   compiler
          option or any previous AUTOMATIC specification.

  AUTOMATIC variables can reduce memory use because only the
  variables currently being used are allocated to memory.

  AUTOMATIC variables permit recursion.  With recursion, a subprogram
  can call itself (directly or indirectly), and resulting values are
  available upon a following call or return to the subprogram.

  9 - BACKSPACE

  Repositions a sequential file that is currently open for sequential
  access to the beginning of the preceding record.  The file must be
  on disk or tape.  Statement format:

     BACKSPACE ([UNIT=]u[,ERR=s][,IOSTAT=ios])
     BACKSPACE u

      u     Is an integer variable or constant specifying the
            logical unit number of the file, optionally prefaced
            by UNIT=.  UNIT= is required if unit is not the
            first I/O specifier.
      s     Is the label of a statement that receives control
            if an error occurs, prefaced by ERR=.
      ios   Is an integer variable to which the completion status
            of the I/O operation is returned, prefaced by IOSTAT=
            (positive if an error occurs, zero if no error occurs).

  A BACKSPACE statement should not be specified for a file that is
  open for direct or append access.  Backspacing from record "n" can
  be done by rewinding to the start of the file and then performing
  n-1 successive reads to reach the previous record.  For direct and
  append access, the current record count ("n") is not available to
  the Fortran I/O system.

  10 - BLOCK_DATA

  Begins a block data program unit.  Statement format:

     BLOCK DATA [nam]

     nam   Is the symbolic name used to identify the block.

  A BLOCK DATA statement and its associated specification statements
  are a special kind of program unit, called a block data subprogram.
  The block data subprogram has the following syntax rules:

     - Any of the following specification statements can appear
       in a block data subprogram:

       COMMON             RECORD
       DATA               SAVE
       DIMENSION          STATIC
       EQUIVALENCE        Structure declaration
       IMPLICIT           Type declaration statements
       PARAMETER

     - A block data subprogram must not contain any
       executable statements.

     - As with other types of program units, the last
       statement in a block data subprogram must be an
       END statement.

     - Within a block data subprogram, if a DATA statement
       initializes any entity in a named common block,
       the subprogram must have a complete set of speci-
       fication statements that establishes the common block.
       However, all the entities in the block do not have
       to be assigned initial values in a DATA statement.

     - One block data subprogram can establish and define
       initial values for more than one common block.

     - The name of a block data subprogram can appear in the
       EXTERNAL statement of a different program unit to force
       a search of object libraries for the BLOCK DATA program
       unit at link time.

  11 - CALL

  Transfers control and passes arguments to a subprogram.

     CALL sub[([a][,[a]]...)]

     sub  Is the name of a subroutine, or other external
          procedure, or a dummy argument associated with
          a subroutine subprogram or other external procedure.

     a    Is a value to be passed to the subroutine.

  If you specify an argument list, the CALL statement associates the
  values in the list with the dummy arguments in the subroutine.  It
  then transfers control to the first executable statement following
  the SUBROUTINE or ENTRY statement referenced by the CALL statement.

  The arguments in the CALL statement must agree in number, order,
  and data type with the dummy arguments in the subroutine.  They can
  be variables, arrays, array elements, records, record elements,
  record arrays, record array elements, substring references,
  constants, expressions, Hollerith constants, alternate return
  specifiers, or subprogram names.  An unsubscripted array name or
  record array name in the argument list refers to the entire array.

  An alternate return specifier is an asterisk (or ampersand)
  followed by the label of a statement in the program unit containing
  the CALL statement.

  Compaq Fortran allows direct or indirect recursive calls to
  subroutines, if you specify the /RECURSIVE compiler option.

  12 - CLOSE

  Closes a file.  Statement format:

     CLOSE ([UNIT=]u[,p][,ERR=s][,IOSTAT=ios])

     u    Is an integer variable or constant specifying the
          logical unit number of the file, optionally prefaced
          by UNIT=.  UNIT= is required if unit is not the
          first I/O specifier.

     p    Is the disposition of the file after closing, prefaced
          by STATUS=, DISPOSE= or DISP=.  Dispositions are as follows:

          'KEEP'             Retains the file.
                               *DEFAULT FOR ALL BUT SCRATCH FILES*
          'SAVE'             Retains the file.
          'DELETE'           Deletes the file.
                               *DEFAULT FOR SCRATCH FILES*
          'PRINT'            Submits the file as a print job.
          'PRINT/DELETE'     Submits then deletes the file as a
                             print job.
          'SUBMIT'           Submits the file as a batch job.
          'SUBMIT/DELETE'    Submits then deletes the file as a
                             batch job.

      s    Is the label of an executable statement.

      ios  Is an integer scalar memory reference.  (Returns a
           zero if no error condition exists or a positive
           integer if an error condition exists.)

  The disposition specified in a CLOSE statement supersedes the
  disposition specified in the OPEN statement, except that a file
  opened as a scratch file cannot be saved, printed, or submitted,
  nor can a file opened for read-only access be deleted.

  13 - COMMON

  Defines one or more contiguous blocks of storage shared among
  separate subprograms.  You can define the same common block in
  different program units of your program.  The first COMMON
  statement in a program unit to name a common block defines it;
  later COMMON statements that name the block reference it.  You can
  leave one common block (the "blank" common block) unnamed.
  Statement format:

     COMMON [/[cb]/]nlist[[,]/[cb]/nlist]...

     cb     Is a symbolic name to identify the common block.

     nlist  Is one or more names of variables, arrays, array
            declarators, or records to identify elements of
            the common block.

  Any common block name, blank or otherwise, can appear more than
  once in one or more COMMON statements in a program unit.  The list
  following each successive appearance of the same common block name
  is treated as a continuation of the list for the block associated
  with that name.

  You can use array declarators in the COMMON statement to define
  arrays.

  A common block can have the same name as a variable, array, record,
  structure, or field.  However, in a program with one or more
  program units, a common block cannot have the same name as a
  function, subroutine, or entry name in the executable program.

  When common blocks from different program units have the same name,
  they share the same storage area when the units are combined into
  an executable program.

  Entities are assigned storage in common blocks on a one-for-one
  basis.  Thus, the entities assigned by a COMMON statement in one
  program unit should agree with the data type of entities placed in
  a common block by another program unit; for example, consider a
  program unit containing the following statement:

     COMMON CENTS

  Consider another program unit containing the following statements:

     INTEGER*2 MONEY
     COMMON MONEY

  When these program units are combined into an executable program,
  incorrect results can occur if the 2-byte integer variable MONEY is
  made to correspond to the lower-addressed two bytes of the real
  variable CENTS.

  14 - CONTINUE

  Transfers control to the next executable statement.  The CONTINUE
  statement is used primarily as the terminal statement of a labeled
  DO loop when that loop would otherwise end improperly with a GOTO,
  arithmetic IF, or other prohibited control statement.  Statement
  format:

     CONTINUE

  15 - DATA

  Assigns values to variables at compile time.  The values within the
  backslashes are assigned to the preceding variables left to right;
  the number of values must equal the number of variable elements.
  Statement format:

     DATA nlist/clist/[[,] nlist/clist]...

     nlist  Is a list combining any combination of variable names,
            array names, array element names, character substring
            names, and implied-DO lists.  (RECORDs are not allowed
            in this list.)  Elements in the list must be separated
            by commas.

            Subscript expressions and expressions in substring
            references must be integer expressions containing
            integer constants and implied-DO variables.

            An implied-DO list in a DATA statement takes the
            following form:

            (dlist, i = n1,n2[,n3])

            dlist     Is a list of one or more array element
                      names, character substring names, or
                      implied-DO lists, separated by commas.

            i         Is the name of an integer variable.

            n1,n2,n3  Are integer constant expressions.  The
                      expression can contain implied-DO variables
                      of other implied-DO lists that have this
                      implied-DO list within their ranges.

     clist  Is a list of constants separated by commas; "clist"
            constants take one of the following forms:

            c OR n *c

            c  Is a constant or the symbolic name of a constant.

            n  Defines the number of times the same value is to
               be assigned to successive entities in the associated
               "nlist"; "n" is a nonzero, unsigned integer constant
               or the symbolic name of an unsigned integer constant.

  The DATA statement assigns the constant values in each "clist" to
  the entities in the preceding "nlist", from left to right, as they
  appear in the "nlist".  The number of constants must equal the
  number of entities in the "nlist".

  When an unsubscripted array name appears in a DATA statement,
  values are assigned to every element of that array in the order of
  subscript progression.  The associated constant list must contain
  enough values to fill the array.

  For more information on the relationship between "nlist" and
  "clist", see your user manual.

  16 - DELETE

  Deletes a record from an indexed or relative file.

  Format -- indexed:

     DELETE ([UNIT=]u[,ERR=s][,IOSTAT=ios])

     Deletes the current record (last record  read)  from  an  indexed
     file.

  Format -- Relative:

     DELETE ([UNIT=]u,REC=r[,ERR=s][,IOSTAT=ios])

     DELETE (u'r[,ERR=s][,IOSTAT=ios])

     Deletes the specified record from a relative file.

     u    Is the logical unit specifier, optionally prefaced
          by UNIT=.  UNIT= is required if unit is not the first
          I/O specifier.

     r    Is a record position specifier, prefaced by REC=.

     u'r  Is a unit and a record position specifier, not
          prefaced by REC=.

     s    Is the label of a statement to which control is
          transferred if an error occurs, prefaced by ERR=.

     ios  Is an I/O status specifier, prefaced by IOSTAT=.

  The forms of the DELETE statement with relative files are direct
  access deletes.  These forms delete the record specified by the
  number "r".

  The DELETE statement logically removes the appropriate record from
  the specified file by locating the record and marking it as a
  deleted record.  A new record can be written into that position.

  Following a direct access delete, any associated variable is set to
  the next record number.

  17 - DICTIONARY

  At compile time, incorporates Oracle Common Data Dictionary
  (CDD/Repository) data definitions into the current Fortran source file.
  The DICTIONARY statement can appear anywhere in a Fortran source file
  that a specification statement is allowed.  Statement format:

     DICTIONARY 'cdd-path [/[NO]LIST]'

     cdd-path   The full or relative pathname of a Common
                Data Dictionary object.  The resulting pathname
                must conform to the rules for forming Common
                Data Dictionary pathnames. The object must be
                a record description.

     /[NO]LIST  Directs the compiler to include (or not include)
                the resulting Fortran source representation in
                the program listing.  /LIST and /NOLIST must be
                spelled completely.

  In the following example, the logical name definition specifies the
  beginning of the CDD pathname; thus, a relative pathname specifies
  the remainder of the path to the record definition:

     $ DEFINE CDD$DEFAULT CDD$TOP.FOR

  The following examples show how a CDD pathname beginning with
  CDD$TOP overrides the default CDD pathname.  Consider a record with
  the pathname CDD$TOP.SALES.JONES.SALARY.  If you defined
  CDD$DEFAULT to be CDD$TOP.SALES.JONES, you could then specify a
  relative pathname:

     DICTIONARY 'SALARY'

  Alternatively, you could specify a full pathname:

     DICTIONARY 'CDD$TOP.SALES.JONES.SALARY'

  18 - DIMENSION

  Defines the number of dimensions in an array and the number of
  elements in each dimension.  Statement format:

     DIMENSION a([d1:]d2)[,a([d1:]d2)]...

     a        Is the symbolic name of the array.  If the array
              is not defined in a data type statement, the array
              takes an implicit data type.

     [d1:]d2  Is the optional lower (d1) and required upper (d2)
              bounds of the array.

  19 - DO

  Executes a block of statements repeatedly until the value of a
  control variable equals, exceeds, or is less than the terminal
  value, according to the control variable specified in the DO loop.
  The block of statements starts immediately following the DO
  statement.

  You can transfer control out of a DO loop, but not out of a
  parallel DO loop.

  Statement format:

     DO [s[,]] v = e1,e2[,e3]

      s   Is the optional label of an executable statement
          that follows the DO statement in the same program unit.
          The label designates the last statement of the DO
          loop. If omitted, an END DO statement is required.

      v   Is the control variable; an integer or real variable
          (it cannot be a record field).  You cannot modify
          the control variable inside the DO loop.

      e1  Is the initial value of the control variable; an
          integer or real value.

      e2  Is the terminal value of the control variable; an
          integer or real value.

      e3  Is the value by which to increment the control
          variable after each execution of the DO loop;
          integer or real value.  It cannot be 0.
          The default of e3 is 1.

  If the iteration count (the number of executions of the DO range)
  is zero or negative, the body of the loop is not executed.  If the
  /NOF77 compiler option is specified and the iteration count is zero
  or negative, the body of the loop is executed once.

  20 - DO_WHILE

  Executes a block of statements repeatedly until the value of a
  logical expression is false.  Statement format:

     DO [s[,]] WHILE (e)

     s  Is the label of an executable statement that follows
        the DO statement in the same program unit. The label
        designates the last statement of the DO loop. If
        omitted, an END DO statement is required.

     e  Is a logical expression.  You can reference and modify
        the variable elements of the expression within the
        DO loop.

  You can transfer control out of a DO WHILE loop but not into a loop
  from elsewhere in the program.

  The DO WHILE statement tests the logical expression at the
  beginning of each execution of the loop, including the first.  If
  the value of the expression is true, the statements in the body of
  the loop are executed; if the expression is false, control
  transfers to the statement following the loop.

  If no label appears in the DO WHILE statement, the DO WHILE loop
  must be terminated with an END DO statement.

  21 - ELSE

  Executes a block of statements if no preceding statement block in a
  block IF construct was executed.  The block of statements starts
  immediately following the ELSE statement.  The block is terminated
  by an END IF statement.  Statement format:

     ELSE

  22 - ELSE_IF

  Executes a block of statements if no preceding statement block in a
  block IF construct was executed and if the value of a logical
  expression is true.  The block of statements starts immediately
  following the ELSE IF statement.  The block is terminated by
  another ELSE IF statement, an ELSE statement, or an END IF
  statement.  Statement format:

     ELSE IF (e) THEN

     Where e represents a logical expression.

  23 - END

  Marks the end of a program unit.  The END statement must be present
  as the last statement of every program unit.  In a main program,
  execution terminates if control reaches the END statement.  In a
  subprogram, a RETURN statement is implicitly executed.  Statement
  format:

     END

  24 - END_DO

  Terminates the block of statements following a DO or DO WHILE
  statement when a label is not used.  Statement format:

     END DO

  25 - END_MAP

  Marks the end of a map declaration within a union declaration in a
  structure declaration block.  Terminates a field declaration or a
  series of field declarations that started with the MAP statement.
  The END MAP statement must be present in a map declaration.
  Statement format:

     END MAP

  26 - END_STRUCTURE

  Marks the end of a structure declaration.  The END STRUCTURE
  statement must be present as the last statement of every structure
  declaration.  Statement format:

     END STRUCTURE

  27 - END_UNION

  Marks the end of a union declaration within a structure declaration
  block.  The END statement must be present as the last statement of
  every union declaration.  Statement format:

     END UNION

  28 - ENDFILE

  Writes an end of file record to a file.  An end of file record
  consists of one byte with the ASCII value 26 (CTRL/Z).  An end-file
  record can be written only to sequential organization files that
  are accessed as formatted sequential files or unformatted segmented
  sequential files.  Statement format:

     ENDFILE ([UNIT=]u[,ERR=s][,IOSTAT=ios])
     ENDFILE u

     u    Is an integer variable or constant specifying
          the logical unit number of the file, optionally
          prefaced by UNIT=.  UNIT= is required if unit is
          not the first I/O specifier.

     s    Is the label of a statement to which control is
          transferred if an error occurs, prefaced by ERR=.

     ios  Is an integer variable to which the completion
          status of the I/O operation is returned, prefaced
          by IOSTAT= (a zero if no error occurs; a positive
          value if an error occurs).

  If the unit specified in the ENDFILE statement is not open, the
  default file is opened for unformatted output.

  An end-of-file record consists of one byte with the ASCII value 26
  (Ctrl/Z).  An end-of-file record can be written only to sequential
  organization files that are accessed as formatted sequential files
  or unformatted segmented sequential files.

  An ENDFILE statement must not be specified for a file that is open
  for direct access.  End-of-file records should not be written in
  files that are read by programs written in a language other than
  Fortran.

  29 - END_IF

  Terminates a block IF construct.  Statement format:

     END IF

  30 - ENTRY

  Designates an alternate entry point at which execution of a
  subprogram can commence.  You cannot use an ENTRY statement in a DO
  loop or a block IF construct.  Statement format:

     ENTRY nam[([p[,p]...])]

     nam  Is a symbolic name for the entry point.  The name
          must be unique among all global names in the program.
          In a function subprogram, the data type defined for
          or implied by the name and the data type of the
          function must be consistent within the following groups:

          Group 1: BYTE, INTEGER*1, INTEGER*2, INTEGER*4,
                   LOGICAL*1, LOGICAL*2, LOGICAL*4, REAL*4,
                   REAL*8, and COMPLEX*8
          Group 2: REAL*16 and COMPLEX*16
          Group 3: CHARACTER

          If the data type is character, the length of the entry
          point name must be the same as the function name or must
          be of passed length.

     p    Is a dummy argument or an alternate return argument
          (designated by an asterisk).  The arguments must agree in
          order, number, and type with the actual arguments of the
          statement invoking the entry point.  The arguments need
          not agree in name, order, number, or type with the
          dummy arguments in the SUBROUTINE or FUNCTION statement
          for the subprogram.  You must use only the dummy arguments
          defined in the ENTRY statement.

  The ENTRY statement is not executable and can appear within a
  function or subroutine program after the FUNCTION or SUBROUTINE
  statement.  Execution of a subprogram referred to by an entry name
  begins with the first executable statement after the ENTRY
  statement.

  31 - EQUIVALENCE

  Starts two or more data elements in one program unit at the same
  storage location, thereby overlaying them in memory.  Statement
  format:

     EQUIVALENCE (nlist)[,(nlist)]...

     nlist  Is a list of variables, array elements, arrays,
            or character substring references, separated by
            commas.  You must specify at least two of these
            entities in each list.

  The elements named within each set of parentheses are given the
  same storage location.  The data elements do not have to be of the
  same type or length.  An equivalency begins with the first byte of
  each element.  When an array or substring element is equivalenced,
  the entire array or string is equivalenced in its normal linear
  storage.

  You cannot equivalence array or string elements in a manner that is
  inconsistent with their normal linear order.  You cannot
  equivalence elements of the same array or string.  You cannot
  equivalence two elements that are both in common areas.

  Records, record fields, and dummy arguments cannot be specified in
  EQUIVALENCE statements.

  You can identify a multidimensional array element by a single
  subscript.  The single subscript designates the absolute position
  of the element within the array.

  32 - EXTERNAL

  Specifies that a name is a global symbol defined outside the
  program unit.  Statement format:

     EXTERNAL v[,v]...
     EXTERNAL *v[,*v]...

     v  Is the symbolic name of a user-supplied subprogram, or
        the name of a dummy argument associated with the name
        of a subprogram.  If you name an intrinsic subprogram,
        that name becomes disassociated from the intrinsic
        subprogram and is assumed to be the name of an external
        element.  (The INTRINSIC statement allows intrinsic
        function names to be used as arguments.)

     *  Is permitted only with the -nof77 option.

  You must use EXTERNAL statements in the following cases:

   -  To identify subprogram or entry point names passed as actual
      arguments

   -  To identify a block data program unit that will reside in a
      library module not explicitly referenced at link time.

  You do not need to use an EXTERNAL statement to identify a
  subprogram or entry point name used as the object of a CALL
  statement or function reference; these names are recognized as
  external implicitly.

  33 - FORMAT

  Defines the conversion of data in formatted data transfer
  operations.  Statement format:

     FORMAT (q1 f1s1 f2s2 ... fnsn qn)

     qn   Is zero or more slash (/) record terminators.

     fn   Is a field descriptor, an edit descriptor, or
          a group of field and edit descriptors enclosed
          in parentheses.

     sn   Is a field separator (a comma or slash).  A
          comma can be omitted in the following cases:

          o Between a P edit descriptor and an immediately
            following F, E, D, or G edit descriptor.

          o Before or after a slash (/) record terminator.

          o Before or after a colon (:) edit descriptor.

  The "field descriptor" has one of the following forms:

     [r]c  [r]cw  [r]cw.m  [r]cw.d[Ee]

     r    Is the optional repeat count.  (If you omit r,
          the repeat count is assumed to be 1.)

     c    Is a format code (I,O,Z,F,E,D,G,L, or A).

     w    Is the external field width in characters.  Each
          data item in the external medium is called an
          external field.

     m    Is the minimum number of characters that must appear
          in the field (including leading zeros).

     d    Is the number of characters to the right of the decimal point.

     E    Is an exponent field.

     e    Is the number of characters in the exponent.

  The terms "r", "w", "m" and "d" must all be unsigned integer
  constants or variable format expressions.  A variable format
  expression is an integer variable or expression enclosed in angle
  brackets that takes the place of an integer constant.  The value of
  the variable or variables can change during program execution.

  The values of "r" and "w" must be in the range of 1 through 32767
  (2**15-1), the values of "m" and "d" must be in the range of 0
  through 255 (2**8-1), and "e" must be in the range of 1 through 255
  (2**8-1).  You cannot use PARAMETER constants for the terms "r",
  "w", "m", "d", or "e".

  The "edit descriptor" has one of the following forms:

     c  [n]c  c[n]

     c     Is a format code (X,T,TL,TR,SP,SS,S,BN,BZ,P,H,Q,'...'
           $, or :).

     n     Is the optional number of characters or character
           positions.

  The term "n" must be an unsigned integer constant (for format code
  P, it can be signed or unsigned) or a variable format expression.
  A variable format expression is an integer variable or expression
  enclosed in angle brackets that takes the place of an integer
  constant.  The value of the variable or variables can change during
  program execution.

  The value of "n" for P must be within the range -128 to 127.  For
  all other format codes, the value of "n" must be within the range 1
  through 65535 (2**16-1); above 65535, the value truncates to 16
  bits.  Note that if you write to a record, it must be able to
  accommodate the size of "n".

  For more detail see Format_Specifiers.

  34 - FUNCTION

  Begins a function subprogram.  Identifies the data type of the
  function and names the dummy arguments.  Format:

     [typ] FUNCTION nam[*m][([p[,p]...])]

     typ  Is a data type.  If you do not specify a data type,
          the data type of the function is implied from its
          name.  If the data type is CHARACTER, you can specify
          CHARACTER*(*) to indicate a passed length function
          type -- the function type assumes the length of its
          definition in the program unit invoking it.

     nam  Is a symbolic name for the function.  The name must be
          unique among all global names in the program.  The name
          is used as a variable within the function.  The value of
          the variable is returned to the caller of the function
          as the value of the function.

     m    Is an unsigned, nonzero integer specifying the length of
          the data type. It must be one of the valid length specifiers
          for "typ".  This length overrides the length specified or
          implied by the type.

     p    Is an unsubscripted variable name specifying a dummy
          argument.  The arguments must agree in order, number, and
          type with the actual arguments of the statement invoking
          the function.  A dummy argument must not be defined as an
          array with more elements than the actual argument holds.

  The array declarator for a dummy argument can itself contain
  integer values that are dummy arguments or are references to a
  common block, providing for adjustable size arrays in functions.
  The upper bound of the array declarator for a dummy argument can be
  specified as an asterisk, in which case the upper bound of the
  dummy argument assumes the size of the upper bound of the actual
  argument.  The size in a character string declarator for a dummy
  argument can be specified as an asterisk in parentheses -- in which
  case the size of the actual argument is passed to the dummy
  argument.

  The values of the actual arguments in the invoking program unit
  become the values of the dummy arguments in the function.  If you
  modify a dummy argument, the corresponding actual argument in the
  invoking program unit is also modified; the actual argument must be
  a variable if it is to be modified.

  If the actual argument is a character constant, the dummy argument
  can be either character or numeric in type, unless the name of the
  subprogram being invoked is a dummy argument in the invoking
  program unit.  If the actual argument is a Hollerith constant, the
  dummy argument must be numeric.

  The FUNCTION statement must be the first statement of a function
  subprogram, unless an OPTIONS statement is specified.  A function
  subprogram cannot contain a SUBROUTINE statement, a BLOCK DATA
  statement, a PROGRAM statement, or another FUNCTION statement.
  ENTRY statements can be included to provide multiple entry points
  to the subprogram.

                                 NOTE

          In a function, the function name identifier  refers
          to  the  return  value,  not  the  function itself,
          unless an argument list is present.  Therefore,  it
          is  not  possible to pass a function as an argument
          to another routine from inside the  function.   For
          example, consider the following:

             INTEGER FUNCTION RECURSIVE_FUNCTION
                .
                .
                .
             CALL OTHERSUB (RECURSIVE_FUNCTION)

          The reference to  RECURSIVE_FUNCTION  in  the  CALL
          statement passes the function return value, not the
          function itself.

  35 - Function Reference

  Transfers control and passes arguments to a function.  Format:

     nam(p[,p]...)

     nam  Is the name of the function or the name of an entry
          point to the function.

     p    Is a value to be passed to the function.  The value
          can be a constant, the name of a variable, the name
          of an array element, the name of an array, an expression,
          a substring, field reference, or the name of a subprogram
          or entry point to a subprogram (must be defined as
          external).  You must not specify more than 255 arguments.

  36 - GOTO

  Transfers control within a program unit.  Depending upon the value
  of an expression, control is transferred either to the same
  statement every time GO TO is executed or to one of a set of
  statements.

 36.1 - Unconditional

  Transfers control unconditionally to the same statement every time
  the GO TO is executed.  Statement format:

     GO TO s

     s  Is the label of an executable statement that is
        in the same program unit as the GO TO statement.

 36.2 - Computed

  Transfers control to a statement based upon the value of an
  expression within the statement.  Statement format:

    GO TO (slist)[,]e

     slist  Is a list of one or more labels of executable
            statements separated by commas. The list of labels
            is called the transfer list.

     e      Is an integer arithmetic expression in the range
            1 to n (where "n" is the number of statement labels
            in the transfer list).

  If the value of e is less than one or greater than the number of
  labels in the transfer list, control is transferred to the first
  executable statement after the computed GO TO.

 36.3 - Assigned

  Transfers control to a statement label that is represented by a
  variable.  An ASSIGN statement must establish a relationship
  between the variable and the specified statement label.  Statement
  format:

     GO TO v[[,](slist)]

     v      Is an integer variable whose value was set by a
            preceding ASSIGN statement in the same program unit.
            (In Compaq Fortran, v must be INTEGER*4.)

     slist  Is a list of one or more labels of executable
            statements separated by commas.

  37 - IF

  Conditionally transfers control or executes a statement or block of
  statements.

  For each type of IF statement, the decision to transfer control or
  to execute the statement or block of statements is based on the
  evaluation of an expression within the IF statement.

 37.1 - Arithmetic

  Executes the statement at the first label if the arithmetic
  expression evaluates to a value less than 0; the statement at the
  second label if the arithmetic expression evaluates to 0; or the
  statement at the third label if the arithmetic expression evaluates
  to a value greater than 0.  Statement format:

     IF (e) s1,s2,s3

     e         Is an arithmetic expression.

     s1,s2,s3  Are labels of executable statements in the same
               program unit.  All three labels are required,
               but they need not refer to different statements.

  Executes the statement at the first label ("s1") if the arithmetic
  expression evaluates to a value less than 0; the statement at the
  second label ("s2") if the arithmetic expression evaluates to 0; or
  the statement at the third label ("s3") if the arithmetic
  expression evaluates to a value greater than 0.

 37.2 - Logical

  Executes the statement if the logical expression is true.
  Statement format:

     IF (e) st

     e   Is a logical expression.

     st  Is a complete Fortran statement. The statement can
         be any statement except DO, END DO, END, block IF,
         or another logical IF statement.

 37.3 - Block

  Executes a block of statements if the logical expression is true.
  The block of statements starts immediately following the IF
  statement.  The block of statements can be followed by optional
  ELSE IF statements (any number) and one optional ELSE statement.
  The entire block IF construct must be terminated by an END IF
  statement.  Format:

     IF (e) THEN
       block
     ELSE IF (e1) THEN
       block
     ELSE
       block
     END IF

     e,e1   Are logical expressions.

     block  Is a series of zero or more Fortran statements
            (called a statement block).

  NOTE:  No additional statement can be placed after the IF THEN
  statement in a block IF construct.  For example, the following
  statement is invalid in the block IF construct:

     IF (e) THEN I = J

  This statement is translated as the following logical IF statement:

     IF (e) THENI = J

  38 - IMPLICIT

  Defines the type specifications of implicitly defined variables.
  Statement format:

     IMPLICIT typ(a[,a]...)[,typ(a[,a]...)]...

     typ  Is any data type except CHARACTER*(*).  When "typ"
          is equal to CHARACTER*len, "len" specifies the length
          for character data type.  The "len" is an unsigned
          integer constant or an integer constant expression
          enclosed in parentheses, and must be in the range of
          1 to 65535.

     a    Is an alphabetical character.  If you specify a
          range of alphabetic characters (two characters
          joined by a hyphen), the first character must be
          less than the second.

  The IMPLICIT statement assigns the specified data type to all
  symbolic names that have no explicit data type and begins with the
  specified letter or range of letters.  It has no effect on the
  default types of intrinsic procedures.

  39 - IMPLICIT_NONE

  Inhibits the implicit declaration of data types in the program
  unit.  When it is used, you must declare the data types of all
  symbols explicitly.  You must not include any other IMPLICIT
  statements in the program unit.  containing an IMPLICIT NONE
  statement.  Statement format:

     IMPLICIT NONE

  NOTE:  To receive warnings when variables are used but not
  declared, you can specify the /WARNINGS=DECLARATIONS compiler
  option instead of IMPLICIT NONE.

  40 - INCLUDE

  Directs the compiler to stop reading statements from the current
  file and read the statements in the included file or module.  When
  it reaches the end of the included file or module, the compiler
  resumes compilation with the next statement after the INCLUDE
  statement.  Statement format:

     INCLUDE 'full-file-name[/[NO]LIST]'

     INCLUDE '[text-lib] (module-name)[/[NO]LIST]'

     full-file-name  Is a character string that specifies
                     the file to be included.  The form of
                     the "full-file-name" must be acceptable
                     to the operating system, as described
                     in your user manual.

     /[NO]LIST    Specifies whether the incorporated code
                  is to appear in the compilation source
                  listing.  In the listing, a number precedes
                  each incorporated statement.  The number
                  indicates the "include" nesting depth of
                  the code. The default is /NOLIST.  /LIST
                  and /NOLIST must be spelled completely.

     text-lib     Is a character string that specifies
                  the "full-file-name" of the text
                  library to be searched.  Its form must
                  be acceptable to the operating system,
                  as described in your user manual.  If
                  "text-lib" is omitted, the specified
                  "module-name" must reside in the default
                  Fortran text library SYS$LIBRARY:FORSYSDEF.TLB,
                  or a user-specified default library.

     module-name  Is the name of the text module, located
                  in a text library, that is to be included.
                  The name of the module must be enclosed
                  in parentheses.  It can be up to 31 char-
                  acters long and can contain any alpha-
                  numeric character and the special char-
                  acters dollar sign ($) and underscore (_).

  The file or module must contain valid Fortran statements.  The file
  or module cannot start with a continuation line, but it can contain
  an INCLUDE statement.

  The limit on nesting depth is 10.

  In the following example, the file COMMON.FOR defines a parameter
  constant M, and defines arrays X and Y as part of the blank common
  block.

     Main Program File              COMMON.FOR File
     -----------------              ---------------
     INCLUDE 'COMMON.FOR'           PARAMETER (M=100)
     DIMENSION Z(M)                 COMMON X(M),Y(M)
     CALL CUBE
     DO 5, I=1,M

  5  Z(I) = X(I)+SQRT(Y(I))
         .
         .
         .
     END

     SUBROUTINE CUBE
     INCLUDE 'COMMON.FOR'
     DO 10, I=1,M
  10 X(I) = Y(I)**3
     RETURN
     END

  41 - Input Output

  Transfer I/O statements include READ, WRITE, REWRITE, ACCEPT, TYPE,
  and PRINT.  Auxiliary I/O statements include OPEN, CLOSE, INQUIRE,
  REWIND, BACKSPACE, ENDFILE, DELETE, and UNLOCK.

  Transfer I/O statements can be formatted (F), unformatted (U),
  list-directed (L-D), or namelist (N) as follows:

     ACCEPT     Sequential -- F, L-D, N
     DELETE     Relative -- U
                Indexed -- U
     PRINT      Sequential -- F, L-D, N
     READ       Sequential -- F, U, L-D, N
                Direct Access -- F, U
                Internal -- F, L-D
                Indexed -- F, U
     REWRITE    Relative -- F, U
                Sequential -- F
                Indexed -- F, U
     TYPE       Sequential -- F, L-D, N
     WRITE      Sequential -- F, U, L-D, N
                Direct Access -- F, U
                Internal -- F, L-D
                Indexed -- F, U

 41.1 - Formatted

  Formatted I/O statements contain explicit format specifiers that
  are used to control the translation of data from internal (binary)
  form within a program to external (readable character) form in the
  records, or vice versa.

  Formatted I/O statements must have a format (FMT=) specified in the
  control list (clist).  Additional "clist" elements are required
  depending on the type of access.

  Formatted sequential READ:

    READ (UNIT=u,FMT=f[,IOSTAT=ios][,ERR=err][,END=end]) [iolist]
    READ f [,iolist]

  Formatted direct access READ:

    READ (UNIT=u,REC=rec,FMT=f[,IOSTAT=ios][,ERR=err]) [iolist]

  Formatted indexed READ:

    READ (UNIT=u,FMT=f,KEY=k[,KEYID=n][,IOSTAT=ios][,ERR=err]) [iolist]

  Formatted internal READ:

    READ (UNIT=u,FMT=f[,IOSTAT=ios][,ERR=err][,END=end]) [iolist]

  Formatted sequential WRITE:

    WRITE (UNIT=u,FMT=f[,IOSTAT=ios][,ERR=err]) [iolist]

  Formatted direct access WRITE:

    WRITE (UNIT=u,REC=rec,FMT=f[,IOSTAT=ios][,ERR=err]) [iolist]

  Formatted indexed WRITE:

    WRITE (UNIT=u,FMT=f[,IOSTAT=ios][,ERR=err]) [iolist]

  Formatted internal WRITE:

    WRITE (UNIT=u,FMT=f[,IOSTAT=ios][,ERR=err]) [iolist]

 41.2 - Unformatted

  Unformatted I/O statements do not contain format specifiers and
  therefore do not translate the data being transferred.

  Unformatted I/O is especially appropriate where the output data
  will later be used as input.  Unformatted I/O saves execution time
  by eliminating the data translation process, preserves greater
  precision in the external data, and usually conserves file storage
  space.

  Unformatted I/O statements do not specify a format (FMT=) in the
  control list (clist).  Other "clist" elements are required
  depending on the type of access.

  Unformatted sequential READ:

    READ (UNIT=u[,IOSTAT=ios][,ERR=err][,END=end]) [iolist]

  Unformatted direct access READ:

    READ (UNIT=u,REC=rec[,IOSTAT=ios][,ERR=err]) [iolist]

  Unformatted indexed READ:

    READ (UNIT=u,KEY=k[,KEYID=n][,IOSTAT=ios][,ERR=err]) [iolist]

  Unformatted sequential WRITE:

    WRITE (UNIT=u,[,IOSTAT=ios][,ERR=err]) [iolist]

  Unformatted direct access WRITE:

    WRITE (UNIT=u,REC=rec[,IOSTAT=ios][,ERR=err]) [iolist]

  Unformatted indexed WRITE:

    WRITE (UNIT=u[,IOSTAT=ios][,ERR=err]) [iolist]

 41.3 - List Directed

  List-directed I/O statements are similar to formatted statements in
  function, but control the translation of data through data types
  instead of explicit format specifiers.

  List-directed I/O statements specify a format (FMT=) in the control
  list (clist).  Other "clist" elements are required depending on the
  type of access.

  List-directed sequential READ:

    READ (UNIT=u,FMT=*[,IOSTAT=ios][,ERR=err][,END=end]) [iolist]
    READ * [,iolist]

  List-directed internal READ

    READ (UNIT=u,FMT=*[,IOSTAT=ios][,ERR=err][,END=end]) [iolist]

  List-directed sequential WRITE

    WRITE (UNIT=u,FMT=*[,IOSTAT=ios][,ERR=err]) [iolist]

  List-directed internal WRITE

    WRITE (UNIT=u,FMT=*[,IOSTAT=ios][,ERR=err]) [iolist]

 41.4 - Namelist

  Namelist I/O statements are similar to formatted statements in
  function, but control the translation of data through data types
  instead of explicit format specifiers.

  Namelist I/O statements do not specify a format (FMT=) in the
  control list (clist).

  Namelist sequential READ:

     READ (UNIT=u,NML=nml[,IOSTAT=ios][,ERR=err][,END=end])
     READ n

  Namelist sequential WRITE:

    WRITE (UNIT=u,NML=nml[,IOSTAT=ios][,ERR=err])

  42 - INQUIRE

  Returns information about specified properties of a file or of a
  logical unit on which a file might be opened.  The unit need not
  exist, nor need it be connected to a file.  If the unit is
  connected to a file, the inquiry encompasses both the connection
  and the file.  Statement format:

     INQUIRE ([FILE=fi][,DEFAULTFILE=dfi...],flist)
     INQUIRE ([UNIT=]u,flist)

     fi     Is a character expression, numeric scalar memory
            reference, or numeric array name reference whose
            value specifies the name of the file to be
            inquired about.

     dfi    Is a character expression specifying a default file
            specification string.  Parts of the file specification
            not specified in FILE are filled in from DEFAULTFILE.
            Parts of the file specification that are still missing
            are filled in from your default directory when the
            program runs.

     flist  Is a list of property specifiers in which any one
            specifier appears only once.  Information about the
            individual specifiers is available under the
            subtopic headings listed at the end of this Help
            topic.

     u      Is an integer variable or constant specifying the
            logical unit number of the file, optionally prefaced
            by UNIT=.  UNIT= is required if unit is not the
            first I/O specifier.  The unit does not have to
            exist, nor does it need to be connected to a file.
            If the unit is connected to a file, the inquiry
            encompasses both the connection and the file.

  FILE=fi and UNIT=u can appear anywhere in the property-specifier
  list; however, if the UNIT keyword is omitted, the unit specifier
  ("u") must be the first parameter in the list.

  When inquiring by file, you can specify DEFAULTFILE=dfi in addition
  to, or in place of, FILE=fi.  If a file is open with both FILE and
  DEFAULTFILE keywords specified in the OPEN statement, then you can
  inquire about this file by specifying both the FILE and DEFAULTFILE
  keywords in the INQUIRE statement.

  An INQUIRE statement can be executed before, during, or after the
  connection of a file to a unit.  The values assigned by the
  statement are those that are current when the INQUIRE statement
  executes.

  You can use INQUIRE to get file characteristics before opening a
  file.  (File characteristics are stored in the file header.)

 42.1 - ACCESS

  ACCESS = acc

  acc  Is a character scalar memory reference that is
       assigned one of the following values:

  'SEQUENTIAL'  If the file is open for sequential access
  'DIRECT'      If the file is open for direct access
  'KEYED'       If the file is open for keyed access
  'UNKNOWN'     If the file is not open

 42.2 - BLANK

  BLANK = blnk

  blnk  Is a character scalar memory reference that is
        assigned one of the following values:

  'NULL'      If null blank control is in effect for the
              file open for formatted I/O.  (Blanks are
              ignored unless the field is all blanks, in
              which case it is treated as zero.)

  'ZERO'      If zero blank control is in effect.  (All
              blanks other than leading blanks are treated
              as zeros.)

  'UNKNOWN'   If the file is not open or if the existing
              file is not open for formatted I/O.

 42.3 - CARRIAGECONTROL

  CARRIAGECONTROL = cc

  cc  Is a character scalar memory reference that is
      assigned one of the following values:

  'FORTRAN'  If the file is open with the FORTRAN carriage
             control
  'LIST'     If the file is open with implied carriage control
             (single spacing between records)
  'NONE'     If the file is open with no carriage control
             attribute
  'UNKNOWN'  If none of the above values apply

 42.4 - CONVERT

  CONVERT = fm

  fm  Is a character scalar memory reference that is assigned
      one of the following values:

      'LITTLE_ENDIAN':  If the file is open with little
                        endian integer and IEEE floating-point
                        data conversion in effect.

      'BIG_ENDIAN':     If the file is open with big endian
                        integer and IEEE floating-point data
                        conversion in effect.

      'CRAY':           If the file is open with big endian
                        integer and CRAY floating-point data
                        conversion in effect.

      'IBM':            If the file is open with big endian
                        integer and IBM System\370 floating-
                        point data conversion in effect.

      'VAXD':           If the file is open with little
                        endian integer and Compaq VAX
                        F_floating and D_floating data
                        conversion in effect.

      'VAXG':           If the file is open with little
                        endian integer and Compaq VAX
                        F_floating and G_floating data
                        conversion in effect.

      'NATIVE':         If the file is open with no data
                        conversion in effect.

      'UNKNOWN':        If the file or unit is not connected
                        for unformatted I/O.

 42.5 - DIRECT

  DIRECT = dir

  dir  Is a character scalar memory reference that is
       assigned one of the following values:

  'YES'       If the file is open for direct access
  'NO'        If the file is not open for direct access
  'UNKNOWN'   If the processor cannot determine whether
              the processor is open for direct access

 42.6 - ERR

  ERR = s

  s  Is the label of an executable statement.

  ERR is a control specifier rather than a property specifier.  If an
  error occurs during the execution of the INQUIRE statement, control
  is transferred to the statement whose label is "s".

 42.7 - EXIST

  EXIST = lv

  lv  Is a logical scalar memory reference that is
      assigned one of the following values:

  .TRUE.    If the specified file exists and can be opened
            or if the unit exists
  .FALSE.   If the specified file or unit does not exist or
            if the file exists but cannot be opened

  The unit exists if it is a number in the range allowed by the
  processor.

 42.8 - FORM

  FORM = fm

  fm  Is a character scalar memory reference that is
      assigned one of the following values:

  'FORMATTED'     If the file is open for formatted I/O
  'UNFORMATTED'   If the file is open for unformatted I/O
  'UNKNOWN'       If no connection exists

 42.9 - FORMATTED

  FORMATTED = fmd

  fmd  Is a character character scalar memory reference that is
       assigned one of the following values:

  'YES'       If formatted I/O is allowed
  'NO'        If formatted I/O is not allowed
  'UNKNOWN'   If the processor cannot determine whether formatted
              I/O is allowed

 42.10 - IOSTAT

  IOSTAT = ios

  ios  Is an integer scalar memory reference.

  IOSTAT is a control specifier rather than a property specifier.
  The "ios" is assigned a processor-dependent positive integer value
  if an error occurs during execution of the INQUIRE statement; it is
  assigned the value zero if there is no error condition.

 42.11 - KEYED

  KEYED = kyd

  kyd  Is a character scalar memory reference that is assigned
       one of the following values:

  'YES'       If keyed access is allowed.
  'NO'        If keyed access is not allowed.
  'UNKNOWN'   If the processor cannot determine whether
              keyed access is allowed

 42.12 - NAME

  NAME = nme

  nme  Is a character scalar memory reference that is
       assigned the name of the file being inquired about.
       If the file does not have a name, "nme" is undefined.

  NOTE:  The FILE and NAME keywords are synonyms when used with the
  OPEN statement, but not when used with the INQUIRE statement.

 42.13 - NAMED

  NAMED = nmd

  nmd  Is a logical scalar memory reference that is
       assigned one of the following values:

  .TRUE.    If the specified file has a name
  .FALSE.   If the file does not have a name

 42.14 - NEXTREC

  NEXTREC = nr

  nr  Is an integer scalar memory reference whose value depends
      on the following conditions:

      - If a record was previously read or written on the
        specified unit, the value of "nr" is one more than the
        number of that record.

      - If no records have been read or written, the value
        of "nr" is 1.

      - If the file is not opened for direct access or if the
        position is indeterminate because of an error condition,
        "nr" is 0.

 42.15 - NUMBER

  NUMBER = num

  num  Is an integer scalar memory reference to which the
       logical unit number of the file is returned.  No value
       is returned if the file is not connected to a unit.

 42.16 - OPENED

  OPENED = od

  od  Is a logical scalar memory reference that is
      assigned one of the following values:

  .TRUE.    If the specified file or unit is open
  .FALSE.   If the specified file or unit is not open

 42.17 - ORGANIZATION

  ORGANIZATION = org

  org  Is a character scalar memory reference that is
       assigned one of the following values:

  'SEQUENTIAL'          If the file is a sequential file
  'RELATIVE'            If the file is a relative file
  'INDEXED' (OpenVMS only)  If the file is an indexed file
  'UNKNOWN'             If the file organization cannot
                           be determined

 42.18 - RECL

  RECL = rcl

  rcl  Is an integer scalar memory reference whose value
       depends on the following conditions:

       - If the file or unit is open, "rcl" is the maximum
         record length allowed in the file

       - If the file is not open, "rcl" is the maximum
         record length allowed in the file; or, if the
         maximum record length is 0, "rcl" is the length
         of the longest record in the file

       - If the file is segmented, "rcl" is the longest
         segment length in the file

       - If the file does not exist, "rcl" is 0.

  The length is expressed in bytes for formatted files and longwords
  for unformatted files.

 42.19 - RECORDTYPE

  RECORDTYPE = rtype

  rtype  Is a character scalar memory reference that is
         assigned one of the following values:

  'FIXED'       If the file is open for fixed-length records
  'VARIABLE'    If the file is open for variable-length records
  'SEGMENTED'   If the file is open for unformatted sequential
                I/O using segmented records
  'STREAM'      If the file's records are not terminated
  'STREAM_CR'   If the file's records are terminated with a
                carriage-return
  'STREAM_LF'   If the file's records are terminated with a
                line-feed
  'UNKNOWN'     If the processor cannot determine the record type

 42.20 - SEQUENTIAL

  SEQUENTIAL = seq

  seq  Is a character scalar memory reference that is
       assigned one of the following values:

  'YES'       If sequential access is allowed for the
              specified file
  'NO'        If sequential access is not allowed
  'UNKNOWN'   If the access mode cannot be determined

 42.21 - UNFORMATTED

  UNFORMATTED = unf

  unf  Is a character scalar memory reference that is
       assigned one of the following values:

  'YES'       If unformatted I/O is allowed for the
              specified file
  'NO'        If unformatted I/O is not allowed
  'UNKNOWN'   If the form cannot be determined

  43 - INTRINSIC

  Specifies that a symbolic name is the name of an intrinsic
  subprogram.  Statement format:

     INTRINSIC v[,v]...

     v  Is the symbolic name of an intrinsic subprogram.

  Subprogram names passed as actual arguments must be identified in
  INTRINSIC statements.  Names of subprograms used as the objects of
  CALL statements or function references do not need to be identified
  with INTRINSIC statements; these names are recognized as intrinsic
  implicitly.

  44 - MAP

  See STRUCTURE (subheads Unions and Type_declarations).

  45 - NAMELIST

  Defines a list of variables or array names and associates that list
  with a unique group-name, which is used in the namelist I/O
  statement.

     NAMELIST/grp/nlist[[,]/grp/nlist]...

     group-name  Is a symbolic name.

     nlist       Is the list of (no more than 250) variable
                 or array names, separated by commas, to be
                 associated with the preceding group-name.

  You cannot include array elements, character substrings, records,
  and record fields in a namelist, but you can use namelist I/O to
  assign values to elements of arrays or substrings of character
  variables that appear in namelists.  Dummy arguments can appear in
  a namelist.

  The namelist entities can have any data type and can be explicitly
  or implicitly typed.

  Only the entities specified in the namelist can be read or written
  in namelist I/O.  It is not necessary for the input records in a
  namelist input statement to define every entity in the associated
  namelist.

  The order of entities in the namelist controls the order in which
  the values are written in the namelist output.  Input of namelist
  values can be in any order.

  A variable or an array name can appear in several namelists.

  46 - OPEN

  Opens an existing file or creates a new file.  If you do not
  explicitly open a file before accessing it, the file is created
  (for write operations) or opened with default attributes.

     OPEN (par[,par]...)

     par  Is a keyword specification in one of the
          following forms:

          keywd
          keywd=value

          keywd  Is a keyword.  (See the subtopic headings
                 listed at the end of this Help topic.)
          value  Is a keyword value. (Some keywords do not
                 have keyword values.)

  If an OPEN statement is executed for a unit that is already open,
  and the file specification is different from that of the current
  open file, the previously opened file is closed and the new file is
  opened.  If the file specification is the same for both files, the
  new value of the BLANK= specifier is in effect, but the position of
  the file is unaffected.

  Keyword specifications can appear in any order.  In most cases,
  they are optional.  Default values apply in their absence.  If the
  logical unit specifier is the first parameter in the list, the UNIT
  keyword is optional.

  You can specify character values at run time by substituting a
  general character expression for a keyword value in the OPEN
  statement.  The character value can contain trailing spaces but not
  leading or embedded spaces; for example:

     CHARACTER*6 FINAL /' '/
         .
         .
         .
     IF (exp) FINAL = 'DELETE'
     OPEN (UNIT=1, STATUS='NEW', DISP=FINAL)

  NOTE:  Keyword values that are numeric expressions can be any
  integer or real expression.  The value of the expression is
  converted to integer data type before it is used in the OPEN
  statement.

 46.1 - ACCESS

  ACCESS = acc

  acc  Is a character expression with one of the following
       values:

  'DIRECT'       Access by record number
  'SEQUENTIAL'   Access sequentially (*DEFAULT*)
  'KEYED'        Access by a specified key
  'APPEND'       Access sequentially, after the last record
                 of the file

 46.2 - ASSOCIATEVARIABLE

  ASSOCIATEVARIABLE = asv

  asv  Is an integer variable.  It cannot be a dummy argument
       to the routine in which the OPEN statement appears.
       Use only in direct access mode.

  NOTE:  Direct access READ, direct access WRITE, FIND, DELETE, and
  REWRITE statements can affect the value of the variable.

 46.3 - BLANK

  BLANK = blnk

  blnk  Is a character expression with one of the following
        values:

  'NULL'  Ignore all blanks in a numeric field (unless the field
          is all blanks, in which case treat blanks as zero).

  'ZERO'  Treat all blanks other than leading blanks as zeros.

  The default is 'NULL'.  However, if you specify the /NOF77 compiler
  option (or OPTIONS /NOF77), the file is implicitly opened, or the
  file is opened for internal I/O, the default is 'ZERO'.

 46.4 - BLOCKSIZE

  BLOCKSIZE = bks

  bks  Is a numeric expression whose value specifies a
       number of bytes.

  For magnetic tape files, the value of "bks" specifies the physical
  record size in the range 18 to 32767 bytes.  The default value is
  2048 bytes.

  For sequential disk files, "bks" is rounded up to an integral
  number of 512-byte blocks and used to specify multiblock transfers.
  The number of blocks transferred can be 1 to 127, and defaults to
  the current count for the device at program run time.

  For indexed and relative files, "bks" is rounded up to an integral
  number of 512-byte blocks and used to specify the RMS bucket size.
  This must fall in the range 1 to 63 blocks, and defaults to the
  smallest value capable of holding one record.

 46.5 - BUFFERCOUNT

  BUFFERCOUNT = bc

  bc  Is a numeric expression whose value specifies
      the number of buffers to be associated with the
      logical unit for multibuffered I/O.  The range
      for "bc" is 1 to 127.

  If you do not specify BUFFERCOUNT or you specify 0, the system
  default is assumed.

 46.6 - CARRIAGECONTROL

  CARRIAGECONTROL = cc

  cc  Is a character expression with one of the following
      values:

  'FORTRAN'   Process with normal FORTRAN interpretation of
              the first character
  'LIST'      Process with single spacing between records
  'NONE'      Do not use implied carriage control

  The default for unformatted files is 'NONE'.  The default for
  formatted files is 'FORTRAN'.

 46.7 - CONVERT

  CONVERT = fm

  fm  Is a character expression with one of the following
      options:

     'LITTLE_ENDIAN'- Little endian integer data of the
                      appropriate size (INTEGER*1, INTEGER*2,
                      or INTEGER*4) and IEEE floating-point
                      data of the appropriate size and
                      type (REAL*4, REAL*8, COMPLEX*8, COMPLEX*16).
                      INTEGER*1 data is the same for little endian
                      and big endian.

     'BIG_ENDIAN' -   Big endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, or INTEGER*4)
                      and IEEE floating-point data of the
                      appropriate size and type (REAL*4, REAL*8,
                      COMPLEX*8, COMPLEX*16).  INTEGER*1 data is
                      the same for little endian and big endian.

     'CRAY' -         Big endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, or INTEGER*4)
                      and CRAY floating-point data of size REAL*8
                      or COMPLEX*16.

     'IBM' -          Big endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, or INTEGER*4)
                      and IBM System\370 floating-point data of
                      size REAL*4 or COMPLEX*8 (IBM short 4)
                      and size REAL*8 or COMPLEX*16 (IBM long 8).

     'VAXD' -         Little endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, or INTEGER*4)
                      and Compaq VAX floating-point data of
                      format F_floating for size REAL*4 or COMPLEX*8,
                      and D_floating for size REAL*8 or COMPLEX*16.

     'VAXG' -         Little endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, or INTEGER*4)
                      and Compaq VAX floating-point data of
                      format F_floating for size REAL*4 or COMPLEX*8,
                      and G_floating for size REAL*8 or COMPLEX*16.

     'NATIVE' -       No data conversion.  This is the default.

  You can use CONVERT to specify multiple formats in a single
  program, usually one format for each specified unit number.

  When reading a non-native format, the non-native format on disk is
  converted to native format in memory.  If a converted non-native
  value is outside the range of the native data type, a run-time
  message appears.

  There are other ways to specify numeric format for unformatted
  files:  you can specify a VMS logical name or the compiler option
  CONVERT (or OPTIONS/CONVERT).  The order of precedence is VMS
  logical name, OPEN (CONVERT=), OPTIONS/CONVERT, and then compiler
  option CONVERT.  The CONVERT compiler option and OPTIONS/CONVERT
  affect all unit numbers used by the program, while logical names
  and OPEN (CONVERT=) affect specific unit numbers.

  The following source code shows how to code the OPEN statement to
  read unformatted CRAY numeric data from unit 15, which might be
  processed and possibly written in little endian format to unit 20:

     OPEN (CONVERT='CRAY', FILE='graph3.dat', FORM='UNFORMATTED',
    1     UNIT=15)
       .
       .
       .
     OPEN (FILE='graph3_native.dat', FORM='UNFORMATTED', UNIT=20)

  For more information on transporting data to or from an OpenVMS VAX
  system and on supported ranges for data types, see your user
  manual.

 46.8 - DEFAULTFILE

  DEFAULTFILE = ce

  ce  Is a character expression that specifies a default file
      specification string.

  This keyword supplies a value to the RMS default file specification
  string for the missing components of a file specification.  If you
  do not specify the DEFAULTFILE keyword, Fortran uses the default
  value 'FORnnn.DAT', where nnn is the unit number with leading
  zeros.

  The default file pathname string is used primarily when accepting
  file specifications interactively.  File specifications known to a
  user program are normally completely specified in the FILE keyword.

  You can specify default values for any one of the following file
  specification components:  node, device, directory, file name, file
  type, and file version number.

  When you specify any of the above components in the FILE keyword,
  they override those values specified in the DEFAULTFILE keyword.

  The following example uses the file name supplied by the user and
  the default file specification supplied by the DEFAULTFILE keyword
  to define the file specification for an existing file:

     TYPE *, 'ENTER NAME OF DOCUMENT'
     ACCEPT *, DOC
     OPEN (UNIT=1, FILE=DOC, DEFAULTFILE='[ARCHIVE].TXT',
    1     STATUS='OLD')

 46.9 - DISPOSE

  DISPOSE = dis
  or DISP = dis

  dis  Is a character expression with one of the following
       values:

  'KEEP' or 'SAVE'  Retain the file after the unit is closed.
                    (*DEFAULT FOR ALL BUT SCRATCH FILES*)

  'DELETE'          Delete the file after the unit is closed.
                    (*DEFAULT FOR SCRATCH FILES*)

  'PRINT'           Submit the file as a print job and retain it.
                    Use this value only with sequential files.

  'PRINT/DELETE'    Submit the file as a print job and then
                    delete it.  Use this value only with sequential
                    files.

  'SUBMIT'          Submit the file as a batch job and retain it.

  'SUBMIT/DELETE'   Submit the file as a batch job and then
                    delete it.

  The disposition specified in a CLOSE statement supersedes the
  disposition specified in the OPEN statement, except that a file
  opened as a scratch file cannot be saved, printed, or submitted,
  nor can a file opened for read-only access be deleted.

 46.10 - ERR

  ERR = s

  s  Is the label of an executable statement that is to receive
     control when an error occurs.

  ERR applies only to the OPEN statement in which it is specified,
  and not in following I/O operations on the unit.  If an error
  occurs, no file is opened or created.  However, you can use IOSTAT
  in following I/O statements to perform a similar function.

 46.11 - EXTENDSIZE

  EXTENDSIZE = e

     e  Is a numeric expression whose value specifies
        the number of blocks to extend a disk file when
        additional file storage is allocated.  The space
        used to extend a file is contiguous if possible
        otherwise, noncontiguous space is used.  Defaults
        to the system default for the device.

 46.12 - FILE

  FILE = fln

  fln  Is a character scalar reference, numeric scalar memory
       reference, or numeric array name reference.

  The FILE parameter specifies the name of the file to be connected
  to the unit.  The name can be any file specification accepted by
  the operating system.

  If the file name is stored in a numeric scalar or array, the name
  must consist of ASCII characters terminated by an ASCII null
  character (zero byte).  However, if it is stored in a character
  scalar or array, it must not contain a zero byte.

 46.13 - FORM

  FORM = ft

  ft  Is a character expression with one of the following
      values:

    'FORMATTED'     Formatted *DEFAULT FOR SEQUENTIAL ACCESS*
    'UNFORMATTED'   Unformatted *DEFAULT FOR DIRECT AND KEYED ACCESS*

 46.14 - INITIALSIZE

  INITIALSIZE = e

     e  Is a numeric expression whose value specifies the
        number of blocks in the initial allocation of space
        for a new file on a disk.  Defaults to no initial allocation.

  If you do not specify INITIALSIZE or if you specify zero, no
  initial allocation is made.  The system attempts to allocate
  contiguous space for INITIALSIZE.  If not enough contiguous space
  is available, noncontiguous space is allocated.

  INITIALSIZE is effective only at the time the file is created.  If
  EXTENDSIZE is specified when the file is created, the value
  specified is the default value used to allocate additional storage
  for the file.  If you specify EXTENDSIZE when you open an existing
  file, the value you specify supersedes any EXTENDSIZE value
  specified when the file was created, and remains in effect until
  you close the file.  Unless specifically overridden, the default
  EXTENDSIZE value is in effect on later openings of the file.

 46.15 - IOSTAT

  IOSTAT = ios

  ios   Is an integer scalar memory reference.

  If no error exists, ios is defined as zero; if an error exists, ios
  is defined as a positive integer.  IOSTAT applies only to the OPEN
  statement in which it appears and not to later I/O operations on
  the logical unit that it opened.  However, you can use the IOSTAT
  parameter in later I/O statements to perform a similar function.

  Secondary operating system messages do not display when IOSTAT is
  specified.  To display these messages, remove IOSTAT or use a
  platform-specific method such as a OpenVMS condition handler.  (For
  more information, see your user manual.)

 46.16 - KEY

  KEY = (kspec[,kspec]...)

  kspec   Takes the following form:

          e1:e2[:dt[:dr]]

          e1   Is the position of the first byte of the
               key in the record.
          e2   Is the position of the last byte of the
               key in the record.
          dt   Is the data type of the key: CHARACTER (*DEFAULT*)
               or INTEGER.
          dr   Is the direction of the key: ASCENDING (*DEFAULT*)
               or DESCENDING.

  The length of the key must not exceed 255 bytes.  The first byte
  position of the key must be at least 1 and the last byte position
  must not exceed the length of the record.

  If the key type is INTEGER, the key length must be either 2 or 4.

  Defining Primary and Alternate Keys:

  You must define at least one key in an indexed file.  This primary
  key is the default key.  It usually has a unique value for each
  record (no duplicates).  Alternate keys can be duplicated.

  You can choose to define alternate keys.  RMS allows up to 254
  alternate keys.  However, individual OPEN statements only allow up
  to 85 key definitions, a number that is further reduced when
  multiple OPEN statements appear together in a program unit.

  If a file requires more keys than the OPEN statement limit, you
  must create it from another language or with the File Definition
  Language (FDL).

  Specifying and Referencing Keys:

  You must specify the KEY parameter when creating an indexed file.
  However, you do not have to respecify it when opening an existing
  file because key attributes are permanent aspects of the file.
  These attributes include key definitions and reference numbers for
  later I/O operations.  If you do choose to specify the KEY
  parameter for an existing file, your specification must be
  identical to the established key attributes.

  Following I/O operations use a reference number, called the
  key-of-reference number, to identify a particular key.  You do not
  specify this number; it is determined by the key's position in the
  specification list:  the primary key is key-of-reference number 0;
  the first alternate key is key-of-reference number 1, and so forth.

 46.17 - MAXREC

  MAXREC = mr

  mr  Is an numeric expression whose value specifies the
      maximum number of records permitted in a direct access
      file.  The default is the maximum allowed (2**32-1).

 46.18 - NAME

  NAME is a nonstandard synonym for FILE.  (See FILE.)

 46.19 - NOSPANBLOCKS

  NOSPANBLOCKS

  Specifies that records are not to cross disk block boundaries.  If
  a record exceeds the size of a physical block, an error occurs.

 46.20 - ORGANIZATION

  ORGANIZATION = org

  org  Is a character expression with one of the following
       values:

  'SEQUENTIAL'  Records are stored in the order that
                they are written. Access mode must be
                sequential, append, or direct (fixed-length
                records only). (*DEFAULT FOR NEW FILES*)

  'RELATIVE'    Records are stored in numbered positions.
                Access mode must be direct or sequential.

  'INDEXED'     Records are stored according to the values
                of their keys. Access mode must be indexed
                or sequential.

  The default for an existing file is its current organization.

 46.21 - READONLY

  READONLY

  Prohibits write access to the file.  Enables users with read access
  but not write access to access the file.

  The Fortran I/O system's default file access privileges are
  read-write, which can cause run-time I/O errors if the file
  protection does not permit write access.

  The READONLY keyword has no effect on the protection specified for
  a file.  Its main purpose is to allow a file to be read
  simultaneously by two or more programs.  For example, if you wish
  to open a file to read the file but want to allow others to read
  the same file while you have it open, specify the READONLY keyword.

 46.22 - RECL

  RECL = rl

  rl  Is an numeric expression whose value indicates the length
      of logical records in a file.

  The value of "rl" does not include space for control information,
  such as for two segment control bytes (if present) or the bytes
  that RMS requires for maintaining record length and deleted record
  control information.  The specification is for record data only.

  The value of "r1" is expressed in units of bytes or longwords,
  depending on the record's format.  Formatted records use byte units
  and unformatted records use longword units (which are equal to 4
  bytes).

  The following are the maximum values that can be specified for "r1"
  for disk files that use the fixed-length record format:

    Sequential formatted               32767 bytes
    Sequential unformatted              8191 longwords
    Relative formatted                 32255 bytes
    Relative unformatted                8063 longwords
    Indexed formatted                  32224 bytes
    Indexed unformatted                 8056 longwords
    Tape formatted                      9999 bytes
    Tape unformatted                    2499 longwords

  For other record formats and device types, the record size limit
  can be less, as described in the "OpenVMS Record Management
  Services Reference Manual".

  RECL is mandatory when opening new files (STATUS='NEW', 'UNKNOWN,
  or 'SCRATCH') and when one or more of the following conditions
  exists:

   o  The record format is fixed length (RECORDTYPE='FIXED').

   o  The file organization is relative or indexed
      (ORGANIZATION='RELATIVE' or 'INDEXED').

   o  The file is opened for direct access (ACCESS='DIRECT').

  RECL is optional in all other cases.  Default values for optional
  cases depend on the value of the RECORDTYPE parameter.

  The following are the RECL default values:

  RECORDTYPE value    RECL value
  ----------------    -----------------------------------------

  'FIXED'             None; value must be explicitly specified.
  All other types     133 bytes (for formatted records)
                      511 longwords (for unformatted records)

  The interpretation and effect of the logical record length varies
  as follows:

   o  If the file contains segmented records, RECL specifies the
      maximum length for any segment (including the two
      segment-control bytes).

   o  If the file contains fixed-length records, RECL specifies the
      size of each record.

   o  If the file contains variable-length records, RECL specifies
      the maximum length for any record.

   o  If your program attempts to write to an existing file a record
      that is longer than the logical record length, an error occurs.

   o  If you are opening an existing file that contains fixed-length
      records or has relative organization and you specify a value
      for RECL that is different from the actual length of the
      records in the file, an error occurs.

 46.23 - RECORDSIZE

  RECORDSIZE = e

  RECORDSIZE is the nonstandard synonym for RECL.

 46.24 - RECORDTYPE

  RECORDTYPE = typ

  typ  Is a character expression with one of the following
       values:

  'FIXED'      All records are one size. Short records are padded
               with blanks (formatted files) or zeros (unformatted
               files).

  'VARIABLE'   Records can vary in length.

  'SEGMENTED'  A record consists of one or more variable length
               records, which can exist in different physical blocks.
               Valid only for unformatted, sequential files with
               sequential access.

  'STREAM'     Data is not grouped into records and contains no
               control information.

  'STREAM_CR'  Variable-length records whose length is indicated by
               carriage-returns embedded in the data.

  'STREAM_LF'  Variable-length records whose length is indicated by
               line-feeds (new lines) embedded in the data.

  When you open a file, default record types are as follows:

  +-------------------------------------+---------------------+
  | File Type                           | Default Record Type |
  +-------------------------------------+---------------------+
  | Relative or indexed files           | 'FIXED'             |
  | Direct access sequential files      | 'FIXED'             |
  | Formatted sequential access files   | 'VARIABLE'          |
  | Unformatted sequential access files | 'SEGMENTED'         |
  +-------------------------------------+---------------------+

  A segmented record consists of one or more variable-length records.
  Using segmented records allows a Fortran logical record to span
  several physical records.  Only unformatted sequential access files
  with sequential organization can use segmented records.  You cannot
  specify <SINGLE_QUOTE>SEGMENTED<SINGLE_QUOTE> for any other file
  type.

  If you do not specify the RECORDTYPE parameter when you are
  accessing an existing file, the record type of the file is used ---
  except for unformatted sequential-access files with sequential
  organization and variable-length records.  These files have a
  default of 'SEGMENTED'.

  If you do specify the RECORDTYPE parameter when you are accessing
  an existing file, the type that you specify must match the type of
  an existing file.

  In fixed-length record files, if an output statement does not
  specify a full record, the record is filled with spaces in a
  formatted file and zeros in an unformatted file.

  You cannot use an unformatted READ statement to access an
  unformatted sequential organization file containing variable-length
  records, unless you specify the corresponding RECORDTYPE value in
  your OPEN statement.

  Files containing segmented records can be accessed only by
  unformatted sequential Fortran I/O statements.

 46.25 - SHARED

  SHARED

  Specifies that the file can be accessed by more than one user at
  the same time.

 46.26 - STATUS

  STATUS = sta

  sta  Is a character expression with one of the following
       values:

  'OLD'       Open an existing file
  'NEW'       Create a new file; if the file already exists an
              error occurs
  'SCRATCH'   Create a new file and delete it when the file is
              closed
  'UNKNOWN'   Open the file as OLD; if it does not exist, then
              open the file as NEW

  The default is 'UNKNOWN'.  However, if you implicitly open a file
  using WRITE, or you specify the /NOF77 compiler option, or OPTIONS
  /NOF77, the default value is 'NEW'.  If you implicitly open a file
  using READ, the default value is 'OLD'.

  Scratch files (STATUS='SCRATCH') are created on the user's default
  disk (SYS$DISK) and are not placed in a directory or given a name
  that is externally visible.  To specify a different device, use the
  FILE keyword.

 46.27 - TYPE

  TYPE is a nonstandard synonym for STATUS (see STATUS).

 46.28 - UNIT

  [UNIT=] u

  u  Is a numeric expression that specifies the logical unit to
     which a file is to be connected.

  The unit specification must appear in the parameter list, unless
  the unit specifier is the first element in the list.

  The logical unit may already be connected to a file when an OPEN
  statement is executed.  If this file is not the same as the one to
  be opened, the OPEN statement executes as if a CLOSE statement had
  executed just before it.

  If the file to be opened is already connected to the unit or if the
  file specifier (FILE keyword) is not included in the OPEN
  statement, only the blank specifier (BLANK keyword) can have a
  value different from the one currently in effect.  The position of
  the file is unaffected.

 46.29 - USEROPEN

  USEROPEN = p

  p  Is the symbolic name of the USEROPEN procedure.
     The USEROPEN parameter specifies a user-written
     EXTERNAL function that controls the opening of
     the file.

  The name must be declared EXTERNAL in the program unit with the
  OPEN statement, and if typed, it must be INTEGER*4.

  47 - OPTIONS

  Overrides qualifiers specified by the FORTRAN command (for a single
  program unit).  Statement format:

   OPTIONS option [option...]

   option  Is one of the following:

     /ASSUME=(ALL, [NO]ACCURACY_SENSITIVE, [NO]DUMMY_ALIASES,
              NONE)
     /NOASSUME

     /BLAS=(ALL, [NO]INLINE, [NO]MAPPED, NONE)
     /NOBLAS

     /CHECK=(ALL, [NO]ALIGNMENT, [NO]ASSERTIONS, [NO]BOUNDS,
             [NO]OVERFLOW, [NO]UNDERFLOW, NONE)
     /NOCHECK

     /CONVERT=(BIG_ENDIAN, CRAY, IBM, LITTLE_ENDIAN, NATIVE,
               VAXD, VAXG)

     /[NO]EXTEND_SOURCE
     /[NO]F77
     /[NO]G_FLOATING
     /[NO]I4
     /[NO]RECURSIVE

  You must place a slash (/) before the option.

  The OPTIONS statement must be the first statement in a program
  unit, preceding the PROGRAM, SUBROUTINE, FUNCTION, and BLOCK DATA
  statements.

  OPTIONS statement options have the same syntax and abbreviations as
  their similarly-named OpenVMS compiler options.

  OPTIONS statement options override compiler options, but only until
  the end of the program unit in which they are defined.  Thus, an
  OPTIONS statement must appear in each program unit in which you
  wish to override the compiler options.

  48 - PARAMETER

  Associates a symbolic name with a constant value.  Statement
  format:

  1.   PARAMETER (p=c [,p=c]...)

     p  Is a symbolic name.

     c  Is a constant, a compile-time expression, or the
        symbolic name of a constant.

  The following additional rules apply to symbolic names:

   -  If the symbolic name is used as the length specifier in a
      CHARACTER declaration, it must be enclosed in parentheses.

   -  If the symbolic name is used as a numeric item in a FORMAT edit
      description, it must be enclosed in angle brackets.

   -  The symbolic name of a constant cannot appear as part of
      another constant, although it can appear as either the real or
      imaginary part of a complex constant.

   -  A symbolic name can be defined only once within the same
      program unit.

   -  You can only use a symbolic name defined to be a constant
      within the program unit containing the defining PARAMETER
      statement.

  The data type of a symbolic name associated with a constant is
  determined as follows:

   -  By an explicit type declaration statement preceding the
      defining PARAMETER statement

   -  By the same rules for implicit declarations that determine the
      data type of any other symbolic name

      For example, the following PARAMETER statement is interpreted
      as MU=1 (MU has an integer data type by implication):

         PARAMETER (MU=1.23)

      If the PARAMETER statement is preceded by an appropriate type
      declaration or IMPLICIT statement, it could be interpreted as
      MU=1.23; for example:

         REAL*8 MU
         PARAMETER (MU=1.23)

  Once a symbolic name is associated with a constant, it can appear
  anywhere in a program that any other constant can appear --- except
  in FORMAT statements (where constants can only be used in variable
  format expressions) and as the character count for Hollerith
  constants.  For compilation purposes, writing the name is the same
  as writing the value.

  A compile-time expression can contain the following intrinsic
  subprograms as long as the operands are constants:  ABS, CHAR,
  CMPLX, CONJG, DIM, DPROD, IAND, ICHAR, IEOR, IMAG, IOR, ISHFT, LGE,
  LGT, LLE, LLT, MIN, MAX, MOD, NINT, and NOT.

  2.     PARAMETER p=c [,p=c]...

     p  Is a symbolic name.

     c  Is a constant, the symbolic name of a constant, or a
        compile-time constant expression.

  This statement is similar to the one described above; they both
  assign a symbolic name to a constant.  However, this PARAMETER
  statement differs from the other one in the following two ways:
  its list is not bounded with parentheses; and the form of the
  constant, rather than implicit or explicit typing of the symbolic
  name, determines the data type of the variable.

  49 - PAUSE

  The PAUSE statement displays a message on the terminal and
  temporarily suspends program execution, so that you can take some
  action.  Statement format:

     PAUSE [disp]

     disp  Is an optional character constant or a string of
           up to six digits.  (FORTRAN-77 limits digits to five.)

  If you do not specify a value for "disp", the system displays the
  following default message:

     FORTRAN PAUSE

  The system then displays the system prompt.

  If you specify a value for "disp", this value is displayed instead
  of the default message.

  EFFECT OF PAUSE IN INTERACTIVE MODE:

  In interactive mode, the program is suspended until you enter one
  of the following commands:

   o  CONTINUE - to resume execution at the next executable
      statement.

   o  DEBUG - to resume execution under control of the OpenVMS
      Debugger.

   o  EXIT - to terminate execution.

      Note that any command, other than CONTINUE or DEBUG, terminates
      execution.

  EFFECT OF PAUSE IN BATCH PROCESS MODE:

  If a program is a batch process, the program is not suspended.  If
  you specify a value for "disp", this value is written to the system
  output file.

  50 - PRINT

  Transfers data from internal storage to FOR$PRINT (normally, the
  terminal in interactive mode or the batch log in batch mode).  The
  access mode is sequential.

 50.1 - Formatted

  Translates data from binary to character format as specified by f.
  Statement format:

     PRINT f[,iolist]

     f       Is a format specifier not prefaced by FMT=.

     iolist  Are the names of the variables from which the
             data is transferred, listed in the order of transfer.

 50.2 - List-directed

  Translates data from binary to character format according to the
  data types of the variables in the I/O list.  Statement format:

     PRINT *[,iolist]

     *       Specifies list-directed formatting.

     iolist  Are the names of the variables from which the data
             is transferred, listed in the order of transfer.

 50.3 - Namelist

  Translates data from binary to character format according to the
  data types of the list entities in the corresponding NAMELIST
  statement.  Statement format:

     PRINT n

     n  Is a namelist group name not prefaced by NML=.

  51 - POINTER

  The POINTER statement establishes pairs of variables and pointers,
  in which each pointer contains the address of its paired variable.
  Statement format:

     POINTER ((pointer,pointee) [,(pointer,pointee)]...

     pointer  Is a variable whose value is used as the
              address of the pointee.

     pointee  Is a variable, array, array declarator, record,
              record array, or record array declarator.

  The following are rules and behavior for the "pointer" argument:

   o  Two pointers can have the same value, so pointer aliasing is
      allowed.

   o  When used directly, a pointer is treated like an integer
      variable.  On VAX systems, a pointer occupies one numeric
      storage unit, so it is a 32-bit quantity (INTEGER*4).

   o  A pointer cannot be pointed to by another pointer; therefore, a
      pointer cannot also be a pointee.

   o  A pointer cannot appear in the following statements:

         ASSIGN       INTRINSIC
         EXTERNAL     PARAMETER

      A pointer can appear in a DATA statement with integer literals
      only.

   o  Integers can be converted to pointers, so you can point to
      absolute memory locations.

   o  A pointer variable cannot be declared to have any other data
      type.

   o  A pointer cannot be a function return value.

   o  You can give values to pointers by using the %LOC built-in
      function to retrieve addresses.  For example:

         integer i(10)
         integer i1 (10) /10*10/
         pointer (p,i)
         p = %loc (i1)
         i(2) = i(2) + 1

   o  The value in a pointer is used as the pointee's base address.

  The following are rules and behavior for the "pointee" argument:

   o  A pointee is not allocated any storage.  References to a
      pointee look to the current contents of its associated pointer
      to find the pointee's base address.

   o  A pointee array can have fixed, adjustable, or assumed
      dimensions.

   o  A pointee cannot appear in the following statements:

         AUTOMATIC       PARAMETER
         COMMON          SAVE
         DATA            STATIC
         EQUIVALENCE     VOLATILE
         NAMELIST

   o  A pointee cannot be a dummy argument.

   o  A pointee cannot be a function return value.

   o  A pointee cannot be a record field or an array element.

  52 - PROGRAM

  Begins a main program.  The PROGRAM statement is optional; when
  used, it can only be preceded by comment lines or an OPTIONS
  statement.  Statement format:

     PROGRAM nam

     nam   Is a symbolic name for the program.  The name must
           be unique among all global names in the program.

  If no PROGRAM statement begins the program, the program name
  defaults to filename$MAIN, where filename is the name of the file
  containing the program.

  53 - READ

  Transfers data from external or internal units to internal storage.

  The meanings of the symbolic abbreviations used to represent the
  parameters in the READ statement syntax are as follows:

     extu     Is the logical unit or internal file optionally
     or       prefaced by UNIT=.  UNIT= is required if unit is
     intu     not the first element in the clist.

     fmt      Specifies whether formatting is to be used for
              data editing, and if it is, the format specification
              or an asterisk (*) to indicate list-directed formatting.
              The "fmt" is optionally prefaced by FMT=, if "fmt" is
              the second parameter in the clist and the first parameter
              is a logical or internal unit specifier without the
              optional keyword UNIT=.

     nml      Is the namelist group specification for namelist I/O.
              Optionally prefaced by NML=.  NML= is required
              if namelist is not the second I/O specifier.

     rec      Is the cell number of a record to be accessed directly.
              Optionally prefaced by REC= or by an apostrophe (').

     iostat   Is the name of a variable to contain the completion
              status of the I/O operation. Optionally prefaced
              by IOSTAT=.

     err      Is the label of a statement to which control is
              transferred in the event of an error. Optionally
              prefaced by ERR=.

     end      Is the label of a statement to which control is
              transferred in the event of an end-of-file.
              Optionally prefaced by END=.

     iolist   Are the names of the variables, arrays, array
              elements, or character substrings from which or
              to which data will be transferred.  Optionally
              an implied-DO list.

     keyspec  Specifies the key of field value of a record to
              be accessed.  Optionally prefaced by KEY=, KEYEQ=,
              KEYGE=, KEYGT=, KEYNXT, KEYNXTNE, KEYLT, or KEYLE.

     keyid    Specifies the key field index that is to be searched
              for the specified key field value. Optionally in-
              cluded with keyspec and optionally prefaced by KEYID=.

  The control-list parameters are "extu" (or "intu"), "fmt", "nml",
  "rec", "iostat", "err", "end", "keyspec", and "keyid".  The I/O
  list parameter is "iolist".

 53.1 - Sequential

 53. 1.1 - Formatted

  Translates the data from character to binary format as specified by
  format specifications.  Statement formats:

  1. READ(extu,fmt[,iostat][,err][,end])[iolist]
     Reads from a specified external unit.

  2. READ f[,iolist]
     Reads from FOR$READ (normally, the terminal).

 53. 1.2 - List-directed

  List-directed sequential READ statement formats:

  1. READ(extu,*[,iostat][,err][,end])[iolist]

     Reads from a specified external unit.
     Translates the data from character to binary
     format according to the data types of the
     variables in the I/O list.

  2. READ *[,iolist]

     Reads from FOR$READ (normally, the terminal).
     Translates the data from character to binary
     format according to the data types of the
     variables in the I/O list.

 53. 1.3 - Namelist

  Namelist sequential READ statement formats:

  1. READ(extu,nml[,iostat][,err][,end])

     Reads from a specified external unit.  Translates
     the data from character to binary format according
     to the data types of the list entities in the
     corresponding NAMELIST statement.

  2. READ nl

     Reads from FOR$READ (normally, the terminal).
     Translates the data from character to binary format
     according to the data types of the entities in the
     corresponding NAMELIST statement.

 53. 1.4 - Unformatted

  Unformatted sequential READ statement format:

     READ(extu,[,iostat][,err][,end])[iolist]

  Reads from a specified external unit.  Does not translate the data.

 53.2 - Direct

 53. 2.1 - Formatted

  Formatted direct READ statement format:

    READ(extu,fmt,rec[,err][,iostat])[iolist]

    READ(u'r,fmt[,err][,iostat]) [iolist]

  Reads from a specified external unit.  Translates the data from
  character to binary format as specified by "fmt".

 53. 2.2 - Unformatted

  Unformatted direct READ statement format:

    READ(extu,rec[,err][,iostat])[iolist]

    READ(u'r[,err][,iostat])[iolist]

  Reads from a specified external unit.  Does not translate the data.

 53.3 - Indexed

 53. 3.1 - Formatted

  Formatted Indexed READ statement format:

    READ(extu,fmt,keyspec[,keyid][,err][,iostat])[iolist]

  Reads from a specified external unit.  Translates the data from
  character to binary format as specified by "fmt".

 53. 3.2 - Unformatted

  Unformatted Indexed READ statement format:

    READ(extu,keyspec[,keyid][,err][,iostat])[iolist]

  Reads from a specified external unit.  Does not translate the data.

 53.4 - Internal

  Internal READ statement format:

    READ(intu,fmt[,err][,iostat][,end])[iolist]

  Reads from a specified character variable.  Translates the data
  from character to binary format as specified by "fmt".

  54 - RECORD

  Creates a record consisting of the variables and arrays specified
  in a previous structure declaration.  Statement format:

    RECORD /str/rnlist[,/str/rnlist...]

     str     Is the name of a previously declared structure.

     rnlist  Is a list of one or more variable names, array
             names, or array declarators, separated by commas.
             All the records named in this list have the
             same structure and are allocated separately in
             memory.

  Record variables can be used in COMMON and DIMENSION statements,
  but not in DATA or EQUIVALENCE statements.

  55 - RETURN

  Transfers control from a subprogram to the calling program.  You
  can only use RETURN in a subprogram unit.  Statement format:

     RETURN [i]

     i  Is an optional integer constant or expression (such
        as 2 or I+J) indicating the position of an alternate
        return from the subprogram in the actual argument list.
        The "i" is converted to an integer value if necessary.

  The argument "i" is valid only for subroutine subprograms.  If no
  alternate return is specified or the specified alternate return
  does not exist in the actual argument list, control returns to the
  statement following the CALL statement.

  If the subprogram is a function, control returns to the statement
  containing the function reference.  If the subprogram is a
  subroutine, control returns either to the statement following the
  CALL statement, or to the label specified by the alternate return
  argument.

  56 - REWIND

  Repositions a sequential file currently open for sequential or
  append access to the beginning of the file.  Do not use a REWIND
  statement for a file that is open for indexed or direct access.
  Allowed only for files on disk or magnetic tape.  Statement format:

     REWIND ([UNIT=]u[,ERR=s][,IOSTAT=ios])
     REWIND u

      u    Is an integer variable or constant specifying the
           logical unit number of the file, optionally prefaced
           by UNIT=.  UNIT= is required if unit is not the first
           I/O specifier.

      s    Is the label of a statement to which control is
           transferred if an error occurs, prefaced by ERR=.

      ios  Is an integer variable to which the completion status
           of the I/O operation is returned, prefaced by IOSTAT=.

  See also BACKSPACE.

  57 - REWRITE

  Transfers data from internal storage and writes the data
  (translated if formatted; untranslated if unformatted) to the
  current record in the following types of files:  an indexed,
  sequential (only if the current record and new record are the same
  length), or relative file.

  The current record is the last record accessed by a preceding,
  successful direct access, indexed, or sequential READ statement.

     Formatted REWRITE statement format:

      REWRITE ([UNIT=]u,[FMT=]f[,ERR=s][,IOSTAT=ios])[iolist]

     Translates the data from binary to character format as
     specified by FMT.

     Unformatted REWRITE statement format:

      REWRITE ([UNIT=]u[,ERR=s][,IOSTAT=ios])[iolist]

     Does not translate the binary data.

     Arguments:

     u       Is an integer variable or constant specifying the
             logical unit number of the file, optionally
             prefaced by UNIT=.  UNIT= is required if unit is
             not the first I/O specifier.

     f       Is a format specifier.

     s       Is the label of a statement to which control is
             transferred if an error condition occurs, prefaced
             by ERR=.

     ios     Is an integer variable to which the completion
             status of the I/O operation is returned, prefaced
             by IOSTAT=.

     iolist  Are the names of the variables from which the data
             is transferred, listed in the order of transfer.
  --------------------------------------------------------------

  Formatted REWRITE Statement Behavior and Errors:

  The formatted REWRITE statement performs the following operations:

   o  It retrieves binary values from internal storage.

   o  It translates those values to character form as specified by
      FORMAT.

   o  It writes the translated data to a current (existing) record in
      a file OPENed with ORGANIZATION='INDEXED', 'RELATIVE', or
      'SEQUENTIAL' (For SEQUENTIAL organization, the new record must
      be the same length as the existing record.)

      The current record is the last record accessed by a preceding,
      successful indexed, direct access, or sequential READ
      statement.

  Errors occur under the following conditions:

   o  If you attempt to rewrite more than one record in a single
      REWRITE statement operation

   o  If a record is too long (Note that unused space in a rewritten,
      fixed-length record is filled with spaces.)

   o  If the primary key value is changed

  In the following example, the REWRITE statement updates the current
  record contained in the relative organization file connected to
  logical unit 3 with the values represented by NAME, AGE, and BIRTH.

           REWRITE (3,10,ERR=99) NAME, AGE, BIRTH
     10    FORMAT (A16,I2,A8)

  -------------------------------------------------------

  Unformatted REWRITE Statement Behavior and Errors:

  The formatted REWRITE statement performs the following operations:

   o  It retrieves binary values from internal storage.

   o  It writes the untranslated data to a current (existing)
      existing record in a file OPENed with ORGANIZATION='INDEXED',
      'RELATIVE', or 'SEQUENTIAL' (For SEQUENTIAL organization, the
      new record must be the same length as the existing record.)

      The current record is the last record accessed by a preceding,
      successful indexed, direct access, or sequential READ
      statement.

  Errors occur under the following conditions:

   o  If you attempt to rewrite more than one record in a single
      REWRITE statement operation

   o  If a record is too long (Note that unused space in a rewritten,
      fixed-length record is filled with zeros.)

   o  If the primary key value is changed

  58 - SAVE

  Declares that the values of data elements are to be saved across
  invocations of a subprogram.  Statement format:

     SAVE [a[,a]...]

     a  Is the symbolic name of a common block (enclosed in
        slashes), a variable, or an array.

  A SAVE statement cannot include a blank common block, names of
  entities in a common block, procedure names, and names of dummy
  arguments.

  Within a program unit, an entity listed in a SAVE statement does
  not become undefined upon execution of a RETURN or END statement
  within that program unit.

  Even though a common block can be included in a SAVE statement,
  individual entities within the common block could become undefined
  (or redefined) in another program unit.

  When a SAVE statement does not explicitly contain a list, it is
  treated as though all allowable items in the program unit are
  specified on the list.

  NOTE:  It is not necessary to use SAVE statements in Compaq Fortran
  programs.  The definitions of data entities are retained
  automatically by default, unless you specify the /RECURSIVE
  compiler option.  (Optimizations can also affect this.  See your
  user manual for more information.) However, the ANSI FORTRAN
  Standard requires using SAVE statements for programs that depend on
  such retention for their correct operation.  If you want your
  programs to be portable, you should include SAVE statements where
  your programs require them.

  The omission of such SAVE statements in necessary instances is not
  flagged, even when you specify the /STANDARD=(SEMANTIC,SYNTAX)
  compiler option, because the compiler does not determine whether
  such dependences exist.

  59 - Statement Function

  Defines a function consisting of a single expression.  The function
  must be invoked from the program unit in which it is defined.
  Format:

     fun([p [,p]...])=e

     fun  Is the symbolic name for the function. You can
          establish its type explicitly or implicitly. The
          value of the expression is returned to the function
          name when the function is invoked.

     p    Is an unsubscripted variable name specifying a
          dummy argument.  The arguments must agree in order,
          number, and type with the actual arguments of the
          statement invoking the function.

     e    Is an arithmetic, logical, or character expression.
          If the expression contains a reference to another
          statement function, the referenced statement
          function must precede the statement function
          containing the reference.

  If you use the name of a dummy argument outside the function
  statement, the name defines another separate data entity.

  Declarator information does not apply to a dummy argument except
  for type.  For example, you cannot define a dummy argument as an
  array or as part of a common block.

  If you use the name of a dummy argument outside the function
  statement, the name defines another separate data entity.

  60 - STOP

  Terminates program execution and writes a message to SYS$OUTPUT.
  Statement format:

     STOP [disp]

     disp  Is a character constant or a string of up to
           six digits.  (FORTRAN-77 limits digits to five.)

  If you specify the optional argument "disp", the STOP statement
  displays the contents of "disp" at your terminal, terminates
  program execution, and returns control to the operating system.

  If you do not specify a value for "disp", the character constant
  FORTRAN STOP is displayed.

  61 - STRUCTURE

  Indicates the beginning of the record structure declaration and
  defines the name of the structure.  Declaration format:

     STRUCTURE [/str/][fnlist]
                fdcl
               [fdcl]
               ...
               [fdcl]
     END STRUCTURE

     str     Identifies a structure name, which is used in
             following RECORD statements to refer to the
             structure. A structure name is enclosed in slashes.

     fnlist  Identifies field names when used in a substructure
             declaration.(Only allowed in nested structure
             declarations.)

     fdcl    (Also called the declaration body.)  Is any
             declaration or combination of declarations of
             substructures, unions, or typed data, or
             PARAMETER statements.

  Following RECORD statements use the structure name to refer to the
  structure.  A structure name must be unique among structure names,
  but structures can share names with variables (scalar or array),
  record fields, PARAMETER constants, and common blocks.

  Structure declarations can be nested (contain one or more other
  structure declarations).  A structure name is required for the
  structured declaration at the outermost level of nesting, and
  optional for the other declarations nested in it.  However, if you
  wish to reference a nested structure in a RECORD statement in your
  program, it must have a name.

  Structure, field, and record names are all local to the defining
  program unit.  When records are passed as arguments, the fields
  must match in type, order, and dimension.

  Unlike type declaration statements, structure declarations do not
  create variables.  Structured variables (records) are created when
  you use a RECORD statement containing the name of a previously
  declared structure.  The RECORD statement can be considered as a
  kind of type statement.  The difference is that aggregate items,
  not single items, are being defined.

  Within a structure declaration, the ordering of both the statements
  and the field names within the statements is important because this
  ordering determines the order of the fields in records.

  In a structure declaration, each field offset is the sum of the
  lengths of the previous fields.  The length of the structure,
  therefore, is the sum of the lengths of its fields.  The structure
  is packed; you must explicitly provide any alignment that is needed
  by including, for example, unnamed fields of the appropriate
  length.

  In the following example, the declaration defines a structure named
  DATE.  This structure contains three scalar fields:  DAY
  (LOGICAL*1), MONTH (LOGICAL*1), and YEAR (INTEGER*2).

     STRUCTURE /DATE/
         LOGICAL*1  DAY, MONTH
         INTEGER*2  YEAR
     END STRUCTURE

 61.1 - Type declarations

  The syntax of a type declaration within a record structure is
  identical to that of a normal Fortran type declaration statement:
  it includes a data type (for example, INTEGER), one or more names
  of variables or arrays; and optionally, one or more data
  initialization values.

  The following rules and behavior apply to type declarations in
  record structures:

   o  %FILL can be specified in place of a field name to leave space
      in a record for purposes such as alignment.  This creates an
      unnamed field.

      %FILL can have an array declarator; for example:

         INTEGER %FILL (2,2)

      Unnamed fields cannot be initialized.  For example, the
      following statement is invalid and generates an error message:

         INTEGER*4 %FILL /1980/

   o  Initial values can be supplied in field declaration statements.
      These initial values are supplied for all records that are
      declared using this structure.  Fields not initialized will
      have undefined values when variables are declared by means of
      RECORD statements.  Unnamed fields cannot be initialized; they
      are always undefined.

   o  Field names must always be given explicit data types.  The
      IMPLICIT statement has no effect on statements within a
      structure declaration.

   o  All Fortran data types are allowed in field declarations.

   o  Any required array dimensions must be specified in the field
      declaration statements.  DIMENSION statements cannot be used to
      define field names.

   o  Adjustable or assumed sized arrays and passed-length CHARACTER
      declarations are not allowed in field declarations.

   o  Field names within the same declaration level must be unique,
      but an inner structure declaration (substructure declaration)
      can include field names used in an outer structure declaration
      without conflict.

 61.2 - Substructure declarations

  A field within a structure can itself be a structured item composed
  of other fields, other structures, or both.  You can declare a
  substructure in two ways:

   o  By nesting structure declarations within other structure or
      union declarations (with the limitation that you cannot refer
      to a structure inside itself at any level of nesting).

      One or more field names must be defined in the STRUCTURE
      statement for the substructure because all fields in a
      structure must be named.  In this case, the substructure is
      being used as a field within a structure or union.

      Field names within the same declaration nesting level must be
      unique, but an inner structure declaration can include field
      names used in an outer structure declaration without conflict.

      %FILL can be specified in place of a field name to leave space
      in a record for purposes such as alignment.

   o  By using a RECORD statement that specifies another previously
      defined record structure, thereby including it in the structure
      being declared.

 61.3 - Union declarations

  A union declaration is a multistatement declaration defining a data
  area that can be shared intermittently during program execution by
  one or more fields or groups of fields.  A union declaration must
  be within a structure declaration.  A union declaration is
  initiated by a UNION statement and terminated by an END UNION
  statement.  Enclosed within these statements are two or more map
  declarations, initiated and terminated by MAP and END MAP
  statements.  Each unique field or group of fields is defined by a
  separate map declaration.

  A union declaration takes the following form:

     UNION
          mdcl
         [mdcl]
         ...
         [mdcl]
     END UNION

     Where "mdcl" represents:

     MAP
        fdcl
       [fdcl]
       ...
       [fdcl]
     END MAP

     fdcl  Is any declaration or combination of declarations
           of substructures, unions, or type declarations.

  As with normal Fortran type declarations, data can be initialized
  in field declaration statements in union declarations.  However, if
  fields within multiple map declarations in a single union are
  initialized, the data declarations are initialized in the order in
  which the statements appear.  As a result, only the final
  initialization takes effect and all the preceding initializations
  are overwritten.

  The size of the shared area established for a union declaration is
  the size of the largest map defined for that union.  The size of a
  map is the sum of the sizes of the fields declared within it.

  As the variables or arrays declared in map fields in a union
  declaration are assigned values during program execution, the
  values are established in a record in the field shared with other
  map fields in the union.  The fields of only one of the map
  declarations are defined within a union at any given point in the
  execution of a program.  However, if you overlay one variable with
  another smaller variable, that portion of the initial variable is
  retained that is not overlaid.  Depending on the application, the
  retained portion of an overlaid variable may or may not contain
  meaningful data and can be used at a later point in the program.

  Manipulating data using union declarations is similar to the effect
  of using EQUIVALENCE statements.  The difference is that data
  entities specified within EQUIVALENCE statements are concurrently
  associated with a common storage location and the data residing
  there; with union declarations you can use one discrete storage
  location to alternately contain a variety of fields (arrays or
  variables).

  With union declarations, only one map declaration within a union
  declaration can be associated at any point in time with the storage
  location that they share.  Whenever a field within another map
  declaration in the same union declaration is referenced in your
  program, the fields in the prior map declaration become undefined
  and are succeeded by the fields in the map declaration containing
  the newly referenced field.

  In the following example, the structure WORDS_LONG is defined.
  This structure contains a union declaration defining two map
  fields.  The first map field consists of three INTEGER*2 variables
  (WORD_0, WORD_1, and WORD_2), and the second, an INTEGER*4
  variable, LONG:

     STRUCTURE /WORDS_LONG/
         UNION
             MAP
              INTEGER*2    WORD_0, WORD_1, WORD_2
             END MAP
             MAP
              INTEGER*4    LONG
             END MAP
         END UNION
     END STRUCTURE

 61.4 - PARAMETER Statements

  PARAMETER statements:  PARAMETER statements can appear in a
  structure declaration, but cannot be given a data type within the
  declaration block.  Consider the following:

     STRUCTURE /ABC/
         INTEGER*4 P
         PARAMETER (P=4)
         REAL*4 F
     END STRUCTURE
         REAL*4 A(P)

  In this example, the INTEGER*4 statement does not provide the data
  type for PARAMETER constant P, but instead declares a record field
  P in structure ABC.  The following PARAMETER statement declares a
  new, different symbol that is given the implicit data type for
  identifiers beginning with the letter P.

  Type declarations for PARAMETER symbolic names must precede the
  PARAMETER statement and be outside of a STRUCTURE declaration, as
  follows:

         INTEGER*4 P
     STRUCTURE /ABC/
         PARAMETER (P=4)
         REAL*4 F
     END STRUCTURE
         REAL*4 A(P)

  For more information on PARAMETER statements, see STATEMENTS
  PARAMETER in this Help file.

  62 - SUBROUTINE

  Begins a subroutine subprogram and names the dummy arguments.  The
  CALL statement transfers control to a subroutine subprogram; a
  RETURN or END statement returns control to the calling program
  unit.  Statement format:

     SUBROUTINE nam[([p[,p]...])]

     nam  Is a symbolic name for the subroutine.  The name must
          be unique among all global names in the program.

     p    Is an unsubscripted variable name specifying a dummy argument.
          An asterisk (*) as a dummy argument specifies that the
          actual argument is an alternate return argument.

  The arguments must agree in order, number, and type with the actual
  arguments of the statement invoking the subroutine.  A dummy
  argument must not be defined as an array with more elements than
  the actual argument holds.  When control transfers to the
  subroutine, the values of any actual arguments in the CALL
  statement are associated with any corresponding dummy arguments in
  the SUBROUTINE statement.  The statements in the subprogram are
  then executed.

  The SUBROUTINE statement must be the first statement of a
  subroutine, unless an OPTIONS statement is specified.

  A subroutine subprogram cannot contain a FUNCTION statement, a
  BLOCK DATA statement, a PROGRAM statement, or another SUBROUTINE
  statement.

  ENTRY statements are allowed to specify multiple entry points in
  the subroutine.

  The array declarator for a dummy argument can itself contain
  integer values that are dummy arguments or are references to a
  common block, providing for adjustable size arrays in subroutines.
  The upper bound of the array declarator for a dummy argument can be
  specified as an asterisk, in which case the upper bound of the
  dummy argument assumes the size of the upper bound of the actual
  argument.  The size in a character string declarator for a dummy
  argument can be specified as an asterisk in parentheses, in which
  case the size of the actual argument is passed to the dummy
  argument.

  The values of the actual arguments in the invoking program unit
  become the values of the dummy arguments in the function.  If you
  modify a dummy argument, the corresponding actual argument in the
  invoking program unit is also modified; the actual argument must be
  a variable if it is to be modified.

  If the actual argument is a character constant, the dummy argument
  can be either character or numeric in type, unless the name of the
  subprogram being invoked is a dummy argument in the invoking
  program unit.  If the actual argument is a Hollerith constant, the
  dummy argument must be numeric.

  63 - TYPE

  Transfers data from internal storage to FOR$TYPE (normally the
  terminal).  The access mode is sequential.

 63.1 - Formatted

  Translates data from binary to character format as specified by the
  format specifications.  Statement format:

     TYPE f[,iolist]

     f       Is a format specifier not prefaced by FMT=.

     iolist  Are the names of the variables from which the
             data is transferred, listed in the order of transfer.

 63.2 - List-directed

  Translates data from binary to character format according to the
  data types of the variables in the I/O list.  Statement format:

     TYPE *[,iolist]

     *       Specifies list-directed formatting.

     iolist  Are the names of the variables from which the data
             is transferred, listed in the order of transfer.

 63.3 - Namelist

  Translates data from binary to character format according to the
  data types of the list entities in the corresponding NAMELIST
  statement.  Statement format:

     TYPE n

     n  Is a namelist group name not prefaced by NML=.

  64 - Type declaration

  A type declaration can be specified only once and must precede all
  executable statements.  A type declaration cannot change the type
  of a symbolic name that has already been implicitly assumed to be
  another type.

  Type declarations must precede all executable statements, can be
  declared only once, and cannot be used to change the type of a
  symbolic name that has already been implicitly assumed to be
  another type.

  Type declaration statements can initialize data in the same way as
  the DATA statement:  by having values, bounded by slashes, listed
  immediately after the symbolic name of the entity.

 64.1 - Numeric

  Format:

     type[*n] v [*n][/clist/][,v [*n][/clist/]]...

     type   Is any of the following data type specifiers:

            BYTE (equivalent to LOGICAL*1 and INTEGER*1)
            DOUBLE PRECISION
            LOGICAL
            INTEGER
            REAL
            COMPLEX
            DOUBLE COMPLEX

     n      Is an integer that specifies (in bytes) the length
            of "v".  It overrides the length that is implied by
            the data type.

            The value of n must specify an acceptable length
            for the type of "v" (see the "DEC Fortran
            Language Reference Manual"). BYTE, DOUBLE
            PRECISION, and DOUBLE COMPLEX data types have
            one acceptable length; thus, for these data types,
            the "n" specifier is invalid.

            If an array declarator is used, the "n" specifier
            must be positioned immediately after the array name.

     v      Is the symbolic name of a constant, variable,
            array, statement function or function
            subprogram, or array declarator.

     clist  Is a list of constants, as in a DATA statement.  If
            "v" is the symbolic name of a constant, the "clist"
            cannot be present.

  A numeric data type declaration statement can define arrays by
  including array declarators in the list.

  A numeric type declaration statement can assign initial values to
  variables or arrays if it specifies a list of constants (the
  "clist").  The specified constants initialize only the variable or
  array that immediately precedes them.  The "clist" cannot have more
  than one element unless it initializes an array.  When the "clist"
  initializes an array, it must contain a value for every element in
  the array.

 64.2 - Character

  Format:

     CHARACTER[*len[,] v[*len] [/clist/] [,v[*len] [/clist/]]...

     len    Is an unsigned integer constant, an integer constant
            expression enclosed in parentheses, or an asterisk (*)
            enclosed in parentheses.  The value of "len" specifies
            the length of the character data elements.

     v      Is the symbolic name of a constant, variable, array,
            statement function or function subprogram, or array
            declarator.  The name can optionally be followed by
            a data type length specifier (*len or *(*)).

     clist  Is a list of constants, as in a DATA statement.  If
            "v" is the symbolic name of a constant, "clist" must
            not be present.

  If you use CHARACTER*len, "len" is the default length specification
  for that list.  If an item in that list does not have a length
  specification, the item's length is "len".  However, if an item
  does have a length specification, it overrides the default length
  specified in CHARACTER*len.

  When an asterisk length specification *(*) is used for a function
  name or dummy argument, it assumes the length of the corresponding
  function reference or actual argument.  Similarly, when an asterisk
  length specification is used for the symbolic name of a constant,
  the name assumes the length of the actual constant it represents.
  For example, STRING assumes a 9-byte length in the following
  statements:

     CHARACTER*(*) STRING
     PARAMETER (STRING = 'VALUE IS:')

  The length specification must range from 1 to 2**31-1 on RISC
  processors.  If no length is specified, a length of 1 is assumed.

  Character type declaration statements can define arrays if they
  include array declarators in their list.  The array declarator goes
  first if both an array declarator and a length are specified.

  A character type declaration statement can assign initial values to
  variables or arrays if it specifies a list of constants (the
  clist).  The specified constants initialize only the variable or
  array that immediately precedes them.  The "clist" cannot have more
  than one element unless it initializes an array.  When the "clist"
  initializes an array, it must contain a value for every element in
  the array.

  65 - UNION

  See Help topic:  (statements) STRUCTURE (subheads Type_declarations
  and Union_declarations).

  66 - UNLOCK

  Frees the current record (that is, the last record read) in an
  indexed, relative, or sequential file.  By default, a record is
  locked when it is read.  The lock is normally held until your
  program performs another I/O operation on the unit (for example,
  rewriting the record, reading another record, or closing the file).
  Statement format:

     UNLOCK ([UNIT=]u[,ERR=s][,IOSTAT=ios])
     UNLOCK u

     u    An integer variable or constant specifying the
          logical unit number of the file, optionally
          prefaced by UNIT=.  UNIT= is required if unit is
          not the first I/O specifier.

     s    The label of a statement to which control is
          transferred if an error condition occurs.

     ios  An integer scalar memory reference that is
          defined as a positive integer if an error occurs
          and zero if no error occurs.

  67 - VOLATILE

  Prevents specified variables, arrays, and common blocks from being
  optimized during compilation.  Statement format:

     VOLATILE nlist

     nlist  Is a list of one or more names of variables, arrays,
            or common blocks (enclosed in slashes), separated
            by commas.

  Variables that have been equivalenced (either directly or
  indirectly) are considered volatile if one element in the
  EQUIVALENCE group is declared volatile.

  If array names or common block names are used, the entire array or
  common block becomes volatile.

  68 - WRITE

  Transfers data from internal storage to external or internal units.

  The meanings of the symbolic abbreviations used to represent the
  parameters in the WRITE statement syntax are as follows:

     extu    Is the logical unit or internal file optionally
     or      prefaced by UNIT=.  UNIT= is required if unit is
     intu    not the first element in the clist.

     fmt     Specifies whether formatting is to be used for data
             editing, and if it is, the format specification or an
             asterisk (*) to indicate list-directed formatting.
             The "fmt" is optionally prefaced by FMT=, if "fmt"
             is the second parameter in the clist and the first
             parameter is a logical or internal unit specifier
             without the optional keyword UNIT=.

     nml     Is the namelist group specification for namelist I/O.
             Optionally prefaced by NML=.  NML= is required if
             namelist is not the second I/O specifier.

     rec     Is the cell number of a record to be accessed directly.
             Optionally prefaced by REC= or by an apostrophe (').

     iostat  Is the name of a variable to contain the completion
             status of the I/O operation. Prefaced by IOSTAT=.

     err     Is the label of a statement to which control is
             transferred in the event of an error. Prefaced by
             ERR=.

     end     Is the label of a statement to which control is
             transferred in the event of an end of file. Prefaced
             by END=.

     iolist  Are the names of the variables, arrays, array elements,
             or character substrings from which or to which data
             will be transferred.  Optionally an implied-DO list.
  .b
  The control-list parameters are "extu" (or "intu"), "fmt", "nml",
  "rec", "iostat", "err", and "end".  The I/O list
  parameter is "iolist".

 68.1 - Sequential

 68. 1.1 - Formatted

  Formatted sequential WRITE statement format:

    WRITE (extu,fmt[,err][,iostat])[iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by "fmt".

 68. 1.2 - List-directed

  List-directed sequential WRITE statement format:

     WRITE (extu,*[,err][,iostat])[iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format according to the data types of the
  variables in the I/O list.

 68. 1.3 - Namelist

  Namelist sequential WRITE statement format:

    WRITE (extu,nml[,err][,iostat])

  Writes to a specified external unit.  Translates the data from
  binary to character format according to the data types of the list
  entities in the corresponding NAMELIST statement.

 68. 1.4 - Unformatted

  Unformatted sequential WRITE statement format:

    WRITE (extu[,err][,iostat])[iolist]

  Writes to a specified external unit.  Does not translate the data.

 68.2 - Direct

 68. 2.1 - Formatted

  Formatted direct WRITE statement format:

    WRITE (extu,rec,fmt[,err][,iostat])[iolist]

    WRITE (u'r,fmt[,err][,iostat]) [iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by fmt.

 68. 2.2 - Unformatted

  Unformatted direct WRITE statement format:

    WRITE (extu,rec[,err][,iostat])[iolist]

    WRITE (u'r[,err][,iostat])[iolist]

  Writes to a specified external unit.  Does not translate the data.

 68.3 - Internal

  Internal WRITE statement format:

    WRITE (intu[,fmt][,err][,iostat])[iolist]

  Writes to a specified character variable.  Translates the data from
  binary to character format as specified by "fmt".

 68.4 - Indexed

 68. 4.1 - Formatted

  Formatted indexed WRITE statement format:

    WRITE (extu,fmt,[,err][,iostat])[iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by "fmt".

 68. 4.2 - Unformatted

  Unformatted indexed WRITE statement format:

    WRITE (extu,[,err][,iostat])[iolist]

  Writes to a specified external unit.  Does not translate the data.
  Close     HLB-list     TLB-list     Help  

[legal] [privacy] [GNU] [policy] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.