VMS Help  —  FORTRAN  Statements
  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 Statements                    |
  |       |--------------------------------------------------------|
  |       |       PROGRAM, FUNCTION, SUBROUTINE, MODULE, or        |
  |       |                BLOCK DATA Statements                   |
  |       |--------------------------------------------------------|
  |       |                    USE Statements                      |
  |       |---------+----------------------------------------------|
  |COMMENT|         |       IMPLICIT NONE Statements               |
  | Lines,|         |------------+-------------------+-------------|
  |INCLUDE|NAMELIST,| PARAMETER  |  IMPLICIT Statements            |
  |State- | FORMAT, |------------+---------------------------------|
  | ments,|   &     |            | Derived-Type Definitions,       |
  |  &    | ENTRY   | PARAMETER  | Interface Blocks, Type          |
  |Direc- | State-  | and DATA   | Declaration Statements, State-  |
  | tives |  ments  | Statements | ment Function Statements, and   |
  |       |         |            | Specification Statements        |
  |       |         +------------+---------------------------------|
  |       |         |   DATA     | Executable Statements           |
  |       |         | Statements |                                 |
  |       |---------+----------------------------------------------|
  |       |                CONTAINS Statement                      |
  |       |--------------------------------------------------------|
  |       |    Internal Subprograms or Module Subprograms          |
  |-------+--------------------------------------------------------|
  |                     END Statement                              |
  +----------------------------------------------------------------+

1  –  Directives

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

1.1  –  General Directives

  HP FORTRAN provides several general-purpose compiler directives
  to perform tasks during compilation.

  General directives begin with the cDEC$ prefix.  These directives
  are enabled in all Fortran compilation units, regardless of the
  options used on the command line.

  The general directives are:

  ALIAS                       MESSAGE
  ATTRIBUTES                  OBJCOMMENT
  DECLARE and NODECLARE       OPTIONS
  DEFINE and UNDEFINE         PACK
  FIXEDFORMLINESIZE           PSECT
  FREEFORM and NOFREEFORM     REAL
  IDENT                       STRICT and NOSTRICT
  IF and IF DEFINED           SUBTITLE and TITLE
  INTEGER                     UNROLL
  IVDEP

  The "c" in the directive prefix (cDEC$) is one of the following:  C
  (or c), !, or *.

  The following are source form rules for directive prefixes:

   o  Prefixes beginning with C (or c) and * are only allowed in
      fixed and tab source forms.

      In these source forms, the prefix must appear in columns 1
      through 5; column 6 must be a blank or tab.  From column 7 on,
      blanks are insignificant, so the directive can be positioned
      anywhere on the line after column 6.

   o  Prefixes beginning with !  are allowed in all source forms.

      The prefix can appear in any valid column, but it cannot be
      preceded by any nonblank characters on the same line.  It can
      only be preceded by whitespace.

  A general directive ends in column 72 (or column 132, if a compiler
  option is specified).

  General directives cannot be continued.

  A comment can follow a directive on the same line.

  Additional Fortran statements (or directives) cannot appear on the
  same line as the general directive.

  General directives cannot appear within a continued Fortran
  statement.

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

1.1.1  –  ALIAS

  cDEC$ ALIAS

  Specifies an alternate external name to be used when referring to
  external subprograms.  It takes the following form:

  cDEC$ ALIAS internal-name, external name

    c               Is one of the following: C (or c), !, or *.

    internal-name   Is the name of the subprogram as used
                    in the current program unit.

    external name   Is a name, or a character constant delimited
                    by quotation marks or apostrophes.

  If a name is specified, the name (in uppercase) is used as the
  external name for the specified "internal-name".  If a character
  constant is specified, it is used as is; the string is not changed
  to uppercase nor are blanks removed.

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

  Names that are not acceptable to the linker will cause link-time
  errors.

  This directive can be useful when compiling applications written
  for other platforms that have different naming conventions.

1.1.2  –  ATTRIBUTES

  cDEC$ ATTRIBUTES

  Lets you specify properties for data objects and procedures.  It
  takes the following form:

  cDEC$ ATTRIBUTES att [,att]... :: object [,object]...

    c        Is one of the following: C (or c), !, or *.

    att      Is one of the following properties:

             ADDRESS64
             ALIAS                        EXTERN
             ALLOW_NULL                   IGNORE_LOC
                                          NO_ARG_CHECK
             C                            NOMIXED_STR_LEN_ARG
             DECORATE                     REFERENCE
             DEFAULT                      REFERENCE32
             DESCRIPTOR                   REFERENCE64
             DESCRIPTOR32                 STDCALL
             DESCRIPTOR64                 VALUE
                                          VARYING

    object   Is the name of a data object or procedure.

  The properties can be used in function and subroutine definitions,
  in type declarations, and with the INTERFACE and ENTRY statements.

  Properties applied to entities available through use or host
  association are in effect during the association.  For example,
  consider the following:

  MODULE MOD1
    INTERFACE
      SUBROUTINE SUB1
      !DEC$ ATTRIBUTES C, ALIAS:'othername' :: NEW_SUB
      END SUBROUTINE
    END INTERFACE
    CONTAINS
      SUBROUTINE SUB2
      CALL NEW_SUB
      END SUBROUTINE
  END MODULE

  In this case, the call to NEW_SUB within SUB2 uses the C and ALIAS
  properties specified in the interface block.

  Options C, STDCALL, REFERENCE, VALUE, and VARYING affect the
  calling conventions of routines:

   o  You can specify C, STDCALL, REFERENCE, and VARYING for an
      entire routine.

   o  You can specify VALUE and REFERENCE for individual arguments.

  For compatibility, !MS$ATTRIBUTES can be used in place of cDEC$
  ATTRIBUTES.

  The properties are described in the following sections.

1.1.2.1  –  ADDRESS64

  Specifies that the data object has a 64-bit address.  This property
  can be specified for any variable or dummy argument, including
  ALLOCATABLE and deferred-shape arrays.  However, variables with
  this property cannot be data-initialized.

  It can also be specified for COMMON blocks or for variables in a
  COMMON block.  If specified for a COMMON block variable, the COMMON
  block implicitly has the ADDRESS64 property.

  ADDRESS64 is not compatible with the AUTOMATIC attribute.

1.1.2.2  –  ALIAS

  Specifies an alternate external name to be used when referring to
  external subprograms.  Its form is:

  ALIAS:external-name

    external-name  Is a character constant delimited by apostrophes
                   or quotation marks.  The character constant is
                   used as is; the string is not changed to uppercase,
                   nor are blanks removed.

  The ALIAS property overrides the C (and STDCALL) property.  If both
  C and ALIAS are specified for a subprogram, the subprogram is given
  the C calling convention, but not the C naming convention.  It
  instead receives the name given for ALIAS, with no modifications.

  ALIAS cannot be used with internal procedures, and it cannot be
  applied to dummy arguments.

  cDEC$ ATTRIBUTES ALIAS has the same effect as the cDEC$ ALIAS
  directive.

1.1.2.3  –  ALLOW_NULL

  Enables a corresponding dummy argument to pass a NULL pointer
  (defined by a zero or the NULL intrinsic function) by value for the
  argument.

  ALLOW_NULL is only valid if the REFERENCE property is also
  specified; otherwise, it has no effect.

1.1.2.4  –  C and STDCALL

  Specify how data is to be passed when you use routines written in C
  or assembler with FORTRAN or Fortran 95/90 routines.

  C and STDCALL are interpreted as synonyms.

  When applied to a subprogram, these properties define the
  subprogram as having a specific set of calling conventions.

  The difference between the calling conventions is this: If C or
  STDCALL is specified for a subprogram, arguments (except for
  arrays and characters) are passed by value.  Subprograms using
  standard Fortran 95/90 conventions pass arguments by reference.

  Character arguments are passed as follows:

   o  By default, hidden lengths are put at the end of the argument
      list.

   o  If C or STDCALL (only) is specified:

      On all systems, the first character of the string is passed
      (and padded with zeros out to INTEGER(4) length).

   o  If C or STDCALL is specified, and REFERENCE is specified for
      the argument:

      On all systems, the string is passed with no length.

   o  If C or STDCALL is specified, and REFERENCE is specified for
      the routine (but REFERENCE is not specified for the argument,
      if any):

      On all systems, the string is passed with the length.

1.1.2.5  –  DECORATE

  Specifies that the external name used in cDEC$ ALIAS or cDEC$
  ATTRIBUTES ALIAS should have the prefix and postfix decorations
  performed on it that are associated with the calling mechanism that
  is in effect.  These are the same decorations performed on the
  procedure name when ALIAS is not specified.

  The case of the external name is not modified.

  If ALIAS is not specified, this property has no effect.

1.1.2.6  –  DEFAULT

  Overrides certain compiler options that can affect external routine
  and COMMON block declarations.

  It specifies that the compiler should ignore compiler options that
  change the default conventions for external symbol naming and
  argument passing for routines and COMMON blocks (/iface, /names,
  and /assume:underscore).

  This option can be combined with other cDEC$ ATTRIBUTES options,
  such as STDCALL, C, REFERENCE, ALIAS, etc.  to specify attributes
  different from the compiler defaults.

  This option is useful when declaring INTERFACE blocks for external
  routines, since it prevents compiler options from changing calling
  or naming conventions.

1.1.2.7  –  DESCRIPTOR

  Specifies that the argument is passed by VMS descriptor.  This
  property can be specified only for dummy arguments in an INTERFACE
  block (NOT for a routine itself).

1.1.2.8  –  DESCRIPTOR32

  Specifies that the argument is passed as a 32-bit descriptor.

1.1.2.9  –  DESCRIPTOR64

  Specifies that the argument is passed as a 64-bit descriptor.

1.1.2.10  –  EXTERN

  Specifies that a variable is allocated in another source file.
  EXTERN can be used in global variable declarations, but it must not
  be applied to dummy arguments.

  EXTERN must be used when accessing variables declared in other
  languages.

1.1.2.11  –  IGNORE_LOC

  Enables %LOC to be stripped from an argument.

  IGNORE_LOC is only valid if the REFERENCE property is also
  specified; otherwise, it has no effect.

1.1.2.12  –  NO_ARG_CHECK

  Specifies that type and shape matching rules related to explicit
  interfaces are to be ignored.  This permits the construction of an
  INTERFACE block for an external procedure or a module procedure
  that accepts an argument of any type or shape; for example, a
  memory copying routine.

  NO_ARG_CHECK can appear only in an INTERFACE block for a
  non-generic procedure or in a module procedure.  It can be applied
  to an individual dummy argument name or to the routine name, in
  which case the property is applied to all dummy arguments in that
  interface.

  NO_ARG_CHECK cannot be used for procedures with the PURE or
  ELEMENTAL prefix.  If an argument has an INTENT or OPTIONAL
  attribute, any NO_ARG_CHECK specification is ignored.

1.1.2.13  –  NOMIXED_STR_LEN_ARG

  Specifies that hidden lengths be placed in sequential order at the
  end of the argument list.

1.1.2.14  –  REFERENCE and VALUE

  Specify how a dummy argument is to be passed.

  REFERENCE specifies a dummy argument's memory location is to be
  passed instead of the argument's value.

  VALUE specifies a dummy argument's value is to be passed instead of
  the argument's memory location.

  When a dummy argument has the VALUE property, the actual argument
  passed to it can be of a different type.  If necessary, type
  conversion is performed before the subprogram is called.

  When a complex (KIND=4, KIND=8, or KIND=16) argument is passed by
  value, two floating-point arguments (one containing the real part,
  the other containing the imaginary part) are passed by immediate
  value.

  Character values, substrings, assumed-size arrays, and adjustable
  arrays cannot be passed by value.

  If REFERENCE (only) is specified for a character argument, the
  string is passed but the length is not passed.

  If REFERENCE is specified for a character argument, and C (or
  STDCALL) has been specified for the routine, the string is passed
  but the length is not passed.  This is true even if REFERENCE is
  also specified for the routine.

  If REFERENCE and C (or STDCALL) are specified for a routine, but
  REFERENCE has not been specified for the argument, the string is
  passed with the length.

  VALUE is the default if the C or STDCALL property is specified in
  the subprogram definition.

1.1.2.15  –  REFERENCE32

  Specifies that the argument is accepted only by 32-bit address.

1.1.2.16  –  REFERENCE64

  Specifies that the argument is accepted only by 64-bit address.

1.1.2.17  –  VARYING

  Allows a variable number of calling arguments.  If VARYING is
  specified, the C property must also be specified.

  Either the first argument must be a number indicating how many
  arguments to process, or the last argument must be a special marker
  (such as -1) indicating it is the final argument.  The sequence of
  the arguments, and types and kinds must be compatible with the
  called procedure.

1.1.3  –  DECLARE and NODECLARE

  cDEC$ DECLARE
  cDEC$ NODECLARE

  The DECLARE directive generates warnings for variables that have
  been used but have not been declared (like the IMPLICIT NONE
  statement).  The NODECLARE directive (the default) disables these
  warnings.

  The "c" in cDEC$ is one of the following:  a C (or c), !, or *.

  The DECLARE directive is primarily a debugging tool that locates
  variables that have not been properly initialized, or that have
  been defined but never used.

  For compatibility, !MS$DECLARE and !MS$NODECLARE can be used in
  place of cDEC$ DECLARE and cDEC$ NODECLARE.

1.1.4  –  DEFINE and UNDEFINE

  cDEC$ DEFINE
  cDEC$ UNDEFINE

  The DEFINE directive creates a symbolic variable whose existence or
  value can be tested during conditional compilation.  The UNDEFINE
  directive removes a defined symbol.

  The DEFINE and UNDEFINE directives take the following forms:

  cDEC$ DEFINE   name [=val]
  cDEC$ UNDEFINE name

    c        Is one of the following: C (or c), !, or *.

    name     Is the name of the variable.

    val      Is an INTEGER(4) value assigned to "name".

  DEFINE and UNDEFINE create and remove variables for use with the IF
  (or IF DEFINED) directive.  Symbols defined with the DEFINE
  directive are local to the directive.  They cannot be declared in
  the Fortran program.

  Because Fortran programs cannot access the named variables, the
  names can duplicate Fortran keywords, intrinsic functions, or
  user-defined names without conflict.

  To test whether a symbol has been defined, use the IF DEFINED
  (name) directive.  You can assign an integer value to a defined
  symbol.  To test the assigned value of "name", use the IF
  directive.  IF test expressions can contain most logical and
  arithmetic operators.

  Attempting to undefine a symbol which has not been defined produces
  a compiler warning.

  The DEFINE and UNDEFINE directives can appear anywhere in a
  program, enabling and disabling symbol definitions.

  For compatibility, !MS$DEFINE and !MS$UNDEFINE can be used in place
  of cDEC$ DEFINE and cDEC$ UNDEFINE.

  Examples:

  Consider the following:

  !DEC$ DEFINE  testflag
  !DEC$ IF DEFINED (testflag)
      write (*,*) 'Compiling first line'
  !DEC$ ELSE
       write (*,*) 'Compiling second line'
  !DEC$ ENDIF
  !DEC$ UNDEFINE  testflag

1.1.5  –  FIXEDFORMLINESIZE

  cDEC$ FIXEDFORMLINESIZE

  Sets the line length for fixed-form source code.  The directive
  takes the following form:

  cDEC$ FIXEDFORMLINESIZE:{72 | 80 | 132}

    c        Is one of the following: C (or c), !, or *.

  You can set FIXEDFORMLINESIZE to 72 (the default), 80, or 132
  characters.  The FIXEDFORMLINESIZE setting remains in effect until
  the end of the file, or until it is reset.

  The FIXEDFORMLINESIZE directive sets the source-code line length in
  include files, but not in USE modules, which are compiled
  separately.  If an include file resets the line length, the change
  does not affect the host file.

  This directive has no effect on free-form source code.

  For compatibility, !MS$FIXEDFORMLINESIZE can be used in place of
  cDEC$ FIXEDFORMLINESIZE.

  Examples:

  Consider the following:

  CDEC$ NOFREEFORM
  CDEC$ FIXEDFORMLINESIZE:132
  WRITE(*,*) 'Text that goes past the 72nd column without continuation'

1.1.6  –  FREEFORM and NOFREEFORM

  cDEC$ FREEFORM
  cDEC$ NOFREEFORM

  The FREEFORM directive specifies that source code is in free-form
  format.  The NOFREEFORM directive specifies that source code is in
  fixed-form format.

  The "c" in cDEC$ is one of the following:  a C (or c), !, or *.

  When the FREEFORM or NOFREEFORM directives are used, they remain in
  effect for the remainder of the file, or until the opposite
  directive is used.  When in effect, they apply to include files,
  but do not affect USE modules, which are compiled separately.

  For compatibility, !MS$FREEFORM and !MS$NOFREEFORM can be used in
  place of cDEC$ FREEFORM and cDEC$ NOFREEFORM.

1.1.7  –  IDENT

  cDEC$ IDENT string

  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" is a character constant containing up to 31 printable
  characters.

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

  IDENT has no effect when you specify the /NOOBJECT compiler option.

1.1.8  –  IF and IFDEFINED

  cDEC$ IF
  cDEC$ IF DEFINED

  The IF and IF DEFINED directives specify a conditional compilation
  construct.  IF tests whether a logical expression is .TRUE.  or
  .FALSE..  IF DEFINED tests whether a symbol has been defined.

  The directive-initiated construct takes the following form:

  cDEC$ IF (expr) [or cDEC$ IF DEFINED (name)]
     block
  [cDEC$ ELSE IF (expr)
     block]...
  [cDEC$ ELSE
     block]
  cDEC$ ENDIF

    c        Is one of the following: C (or c), !, or *.

    exp      A logical expression that evaluates to .TRUE.
             or .FALSE..

    name     Is the name of a symbol to be tested for definition.

    block    Are executable statements that are compiled (or not)
             depending on the value of logical expressions in
             the IF directive construct.

  The IF and IF DEFINED directive constructs end with an ENDIF
  directive and can contain one or more ELSEIF directives and at most
  one ELSE directive.  If the logical condition within a directive
  evaluates to .TRUE.  at compilation, and all preceding conditions
  in the IF construct evaluate to .FALSE., then the statements
  contained in the directive block are compiled.

  A "name" can be defined with a DEFINE directive, and can optionally
  be assigned an integer value.  If the symbol has been defined, with
  or without being assigned a value, IF DEFINED (name) evaluates to
  .TRUE.; otherwise, it evaluates to .FALSE..

  If the logical condition in the IF or IF DEFINED directive is
  .TRUE., statements within the IF or IF DEFINED block are compiled.
  If the condition is .FALSE., control transfers to the next ELSEIF
  or ELSE directive, if any.

  If the logical expression in an ELSEIF directive is .TRUE.,
  statements within the ELSEIF block are compiled.  If the expression
  is .FALSE., control transfers to the next ELSEIF or ELSE directive,
  if any.

  If control reaches an ELSE directive because all previous logical
  conditions in the IF construct evaluated to .FALSE., the statements
  in an ELSE block are compiled unconditionally.

  You can use any Fortran logical or relational operator or symbol in
  the logical expression of the directive.  The logical expression
  can be as complex as you like, but the whole directive must fit on
  one line.

  For compatibility, each directive in the construct can begin with
  the prefix !MS$ instead of cDEC$.

  Examples:

  Consider the following:

  ! When the following code is compiled and run,
  !  the output depends on whether one of the expressions
  !  tests .TRUE.; or all test .FALSE.

  !DEC$ DEFINE flag=3
  !DEC$ IF (flag .LT. 2)
     WRITE (*,*) "This is compiled if flag less than 2."
  !DEC$ ELSEIF (flag >= 8)
     WRITE (*,*) "Or this compiled if flag greater than &
                  or equal to 8."
  !DEC$ ELSE
     WRITE (*,*) "Or this compiled if all preceding &
                  conditions .FALSE."
  !DEC$ ENDIF
  END

1.1.9  –  INTEGER

  cDEC$ INTEGER

  Specifies the default integer kind.  It takes the following form:

  cDEC$ INTEGER:{2 | 4 | 8}

    c        Is one of the following: C (or c), !, or *.

  The INTEGER directive specifies a size of 2 (KIND=2), 4 (KIND=4),
  or 8 (KIND=8) bytes for default integer numbers.

  When the INTEGER directive is effect, all default integer variables
  are of the kind specified in the directive.  Only numbers specified
  or implied as INTEGER without KIND are affected.

  The INTEGER directive can only appear at the top of a program unit.
  A program unit is a main program, an external subroutine or
  function, a module or a block data program unit.  The directive
  cannot appear between program units, or at the beginning of
  internal subprograms.  It does not affect modules invoked with the
  USE statement in the program unit that contains it.

  The default logical kind is the same as the default integer kind.
  So, when you change the default integer kind you also change the
  default logical kind.

  For compatibility, !MS$INTEGER can be used in place of cDEC$
  INTEGER.

  Examples:

  Consider the following:

  INTEGER i              ! a 4-byte integer
  WRITE(*,*) KIND(i)
  CALL INTEGER2( )
  WRITE(*,*) KIND(i)     ! still a 4-byte integer
                         !   not affected by setting in subroutine
  END
  SUBROUTINE INTEGER2( )
     !DEC$ INTEGER:2
     INTEGER j           ! a 2-byte integer
     WRITE(*,*) KIND(j)
  END SUBROUTINE

1.1.10  –  IVDEP

  cDEC$ IVDEP

  The IVDEP directive assists the compiler's dependence analysis.  It
  can only be applied to iterative DO loops.  This directive can also
  be specified as INIT_DEP_FWD (INITialize DEPendences ForWarD).

  The IVDEP directive takes the following form:

  cDEC$ IVDEP

    c        Is one of the following: C (or c), !, or *.

  The IVDEP directive is an assertion to the compiler's optimizer
  about the order of memory references inside a DO loop.

  The IVDEP directive tells the compiler to begin dependence analysis
  by assuming all dependences occur in the same forward direction as
  their appearance in the normal scalar execution order.  This
  contrasts with normal compiler behavior, which is for the
  dependence analysis to make no initial assumptions about the
  direction of a dependence.

  The IVDEP directive must precede the DO statement for each DO loop
  it affects.  No source code lines, other than the following, can be
  placed between the IVDEP directive statement and the DO statement:

   o  An UNROLL directive

   o  Placeholder lines

   o  Comment lines

   o  Blank lines

  The IVDEP directive is applied to a DO loop in which the user knows
  that dependences are in lexical order.  For example, if two memory
  references in the loop touch the same memory location and one of
  them modifies the memory location, then the first reference to
  touch the location has to be the one that appears earlier lexically
  in the program source code.  This assumes that the right-hand side
  of an assignment statement is "earlier" than the left-hand side.

  The IVDEP directive informs the compiler that the program would
  behave correctly if the statements were executed in certain orders
  other than the sequential execution order, such as executing the
  first statement or block to completion for all iterations, then the
  next statement or block for all iterations, and so forth.  The
  optimizer can use this information, along with whatever else it can
  prove about the dependences, to choose other execution orders.

  Examples:

  In the following example, the IVDEP directive provides more
  information about the dependences within the loop, which may enable
  loop transformations to occur:

  !DEC$ IVDEP
        DO I=1, N
           A(INDARR(I)) = A(INDARR(I)) + B(I)
        END DO

  In this case, the scalar execution order follows:

  1.  Retrieve INDARR(I).

  2.  Use the result from step 1 to retrieve A(INDARR(I)).

  3.  Retrieve B(I).

  4.  Add the results from steps 2 and 3.

  5.  Store the results from step 4 into the location indicated by
      A(INDARR(I)) from step 1.

  IVDEP directs the compiler to initially assume that when steps 1
  and 5 access a common memory location, step 1 always accesses the
  location first because step 1 occurs earlier in the execution
  sequence.  This approach lets the compiler reorder instructions, as
  long as it chooses an instruction schedule that maintains the
  relative order of the array references.

1.1.11  –  MESSAGE

  cDEC$ MESSAGE

  Specifies a character string to be sent to the standard output
  device during the first compiler pass; this aids debugging.

  This directive takes the following form:

  cDEC$ MESSAGE:string

    c        Is one of the following: C (or c), !, or *.

    string   Is a character constant specifying a message.

  For compatibility, !MS$MESSAGE can be used in place of cDEC$
  MESSAGE.

  Examples:

  Consider the following:

  !DEC$ MESSAGE:'Compiling Sound Speed Equations'

1.1.12  –  OBJCOMMENT

  cDEC$ OBJCOMMENT

  Specifies a library search path in an object file.  This directive
  takes the following form:

  cDEC$ OBJCOMMENT LIB:library

    c        Is one of the following: C (or c), !, or *.

    library  Is a character constant specifying the name
             and, if necessary, the path of the library
             that the linker is to search.

  The linker searches for the library named by the OBJCOMMENT
  directive as if you named it on the command line, that is, before
  default library searches.  You can place multiple library search
  directives in the same source file.  Each search directive appears
  in the object file in the order it is encountered in the source
  file.

  If the OBJCOMMENT directive appears in the scope of a module, any
  program unit that uses the module also contains the directive, just
  as if   the OBJCOMMENT directive appeared in the source file using
  the module.

  If you want to have the OBJCOMMENT directive in a module, but do
  not want it in the program units that use the module, place the
  directive outside the module that is used.

  For compatibility, !MS$OBJCOMMENT can be used in place of cDEC$
  OBJCOMMENT.

  Examples:

  Consider the following:

  ! MOD1.F90
  MODULE a
     !DEC$ OBJCOMMENT LIB: "opengl32.lib"
  END MODULE a

  ! MOD2.F90
  !DEC$ OBJCOMMENT LIB: "graftools.lib"
  MODULE b
     !
  END MODULE b

  ! USER.F90
  PROGRAM go
     USE a      ! library search contained in MODULE a
                !   included here
     USE b      ! library search not included
  END

1.1.13  –  OPTIONS

  cDEC$ OPTIONS

  Affects data alignment and warnings about data alignment.  The
  OPTIONS directive takes the following form:

  cDEC$ OPTIONS option [option]
    ...
  cDEC$ END OPTIONS

    c       Is one of the following: C (or c), !, or *.

    option  Is one or both of the following:

    o /WARN=[NO]ALIGNMENT

    Controls whether warnings are issued by the compiler for
    data that is not naturally aligned.  By default, you receive
    compiler messages when misaligned data is encountered
    (/WARN=ALIGNMENT).

    o /[NO]ALIGN[=p]

    Controls whether the VSI Fortran compiler naturally aligns
    fields in derived-type and record structures and data items
    in common blocks for performance reasons, or whether the
    compiler packs those fields and data items together on
    arbitrary byte boundaries.

    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 derived-type and record structures)
         STRUCTURES (a synonym for RECORDS)

     rule   Is one of the following keywords:

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

            NATURAL -  Naturally aligns fields in structures
                       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 INTEGER*8, 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; so, 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, VSI Fortran always aligns local data
  items on natural boundaries.  However, EQUIVALENCE, COMMON, RECORD,
  and STRUCTURE data declaration statements can force misaligned
  data.  If /WARN=NOALIGNMENT is specified, warnings will not be
  issued if misaligned data is encountered.

                                 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.

  To request packed, unaligned data in a record structure, specify
  /ALIGN=RECORDS=PACKED, or consider placing source data declarations
  for the record so that the data 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 the HP
  Fortran for OpenVMS User Manual.

1.1.14  –  PACK

  cDEC$ PACK

  Specifies the memory starting addresses of derived-type items.  It
  takes the following form:

  cDEC$ PACK:[{1 | 2 | 4}]

    c        Is one of the following: C (or c), !, or *.

  Items of derived types and record structures are aligned in memory
  on the smaller of two sizes:  the size of the type of the item, or
  the current alignment setting.  The current alignment setting can
  be 1, 2, 4, or 8 bytes.  The default initial setting is 8 bytes
  (unless a compiler option specifies otherwise).  By reducing the
  alignment setting, you can pack variables closer together in
  memory.

  The PACK directive lets you control the packing of derived-type or
  record structure items inside your program by overriding the
  current memory alignment setting.

  For example, if CDEC$ PACK:1 is specified, all variables begin at
  the next available byte, whether odd or even.  Although this
  slightly increases access time, no memory space is wasted.  If
  CDEC$ PACK:4 is specified, INTEGER(1), LOGICAL(1), and all
  character variables begin at the next available byte, whether odd
  or even.  INTEGER(2) and LOGICAL(2) begin on the next even byte;
  all other variables begin on 4-byte boundaries.

  If the PACK directive is specified without a number, packing
  reverts to the compiler option setting (if any), or the default
  setting of 8.

  The directive can appear anywhere in a program before the
  derived-type definition or record structure definition.  It cannot
  appear inside a derived-type or record structure definition.

  For compatibility, !MS$PACK can be used in place of cDEC$ PACK.

  Examples:

  Consider the following:

  ! Use 4-byte packing for this derived type
  ! Note PACK is used outside of the derived-type definition
  !DEC$ PACK:4
  TYPE pair
    INTEGER a, b
  END TYPE
  ! revert to default or compiler option
  !DEC$ PACK:

1.1.15  –  PSECT

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

  Lets you modify several characteristics of a common block.

  Specify the name of a common block, preceded and followed by a
  slash, and one of the following keywords ("attr"):

   o  ALIGN=val or ALIGN=keyword

      Specifies alignment for the common block.

      "val" must be a constant ranging from 0 through 16.

      The specified number is interpreted as a power of 2.  The value
      of the expression is the alignment in bytes.

      "keyword" is one of the following:

            Keyword        Equivalent to "val"
            BYTE               0
            WORD               1
            LONG               2
            QUAD               3
            OCTA               4
            PAGE [see note]    Alpha: 16
                               Intel: 12

        note: Range for Alpha is 0 to 16; for
              Intel, 0 to 12.

      The default is octaword alignment (4).

   o  GBL

      Specifies global scope.  This is the default scope.

   o  LCL

      Specifies local scope.  This keyword is opposite to GBL and
      cannot appear with it.

   o  [NO]MULTILANGUAGE

      Controls whether the compiler pads the size of overlaid psects
      (program sections) to ensure compatibility when the psect is
      shared by code created by other OpenVMS compilers.

      When a psect generated by a Fortran common block is overlaid
      with a psect consisting of a C structure, linker error messages
      can occur.  This is because the sizes of the psects are
      inconsistent; the C structure is padded, but the Fortran common
      block is not.

      Specifying MULTILANGUAGE ensures that VSI Fortran follows a
      consistent psect size allocation scheme that works with HP
      C psects shared across multiple images.  Psects shared in a
      single image do not have a problem.

      The default is NOMULTILANGUAGE.  This is also the default
      behavior of HP Fortran 77 and is sufficient for most
      applications.

      To specify MULTILANGUAGE for all COMMON blocks in a module, use
      compiler option /ALIGN=COMMON=MULTILANGUAGE.  (For more
      information, see the HP Fortran for OpenVMS User Manual.)

   o  [NO]SHR

      Determines whether the contents of a common block can be shared
      by more than one process.  The default is NOSHR.

   o  [NO]WRT

      Determines whether the contents of a common block can be
      modified during program execution.  The default is WRT.

  Global or local scope is significant for an image that has more
  than one cluster.  Program sections with the same name that are
  from different modules in different clusters are placed in separate
  clusters if local scope is in effect.  They are placed in the same
  cluster if global scope is in effect.

  If one program unit changes one or more characteristics of a common
  block, all other units that reference that common block must also
  change those characteristics in the same way.

  Default characteristics apply if you do not modify them with a
  PSECT directive.

  See the "OpenVMS Linker Utility Manual" for detailed information
  about default attributes of common blocks.

1.1.16  –  REAL

  cDEC$ REAL

  Specifies the default real kind.  It takes the following form:

  cDEC$ REAL:{4 | 8 | 16}

    c        Is one of the following: C (or c), !, or *.

  The REAL directive specifies a size of 4 (KIND=4), 8 (KIND=8), or
  16 (KIND=16) bytes for default real numbers.

  When the REAL directive is effect, all default real variables are
  of the kind specified in the directive.  Only numbers specified or
  implied as REAL without KIND are affected.

  The REAL directive can only appear at the top of a program unit.  A
  program unit is a main program, an external subroutine or function,
  a module or a block data program unit.  The directive cannot appear
  between program units, or at the beginning of internal subprograms.
  It does not affect modules invoked with the USE statement in the
  program unit that contains it.

  For compatibility, !MS$REAL can be used in place of cDEC$ REAL.

  Consider the following:

  REAL r               ! a 4-byte REAL
  WRITE(*,*) KIND(r)
  CALL REAL8( )
  WRITE(*,*) KIND(r)   ! still a 4-byte REAL
                       !  not affected by setting in subroutine
  END
  SUBROUTINE REAL8( )
     !DEC$ REAL:8
     REAL s            ! an 8-byte REAL
     WRITE(*,*) KIND(s)
  END SUBROUTINE

1.1.17  –  STRICT and NOSTRICT

  cDEC$ STRICT
  cDEC$ NOSTRICT

  The STRICT directive disables language features not found in the
  language standard specified on the command line (Fortran 95 or
  Fortran 90).  The NOSTRICT directive (the default) enables these
  language features.

  The "c" in cDEC$ is one of the following:  a C (or c), !, or *.

  If STRICT is specified and no language standard is specified on the
  command line, the default is to disable features not found in
  Fortran 90.

  The STRICT and NOSTRICT directives can appear only appear at the
  top of a program unit.  A program unit is a main program, an
  external subroutine or function, a module or a block data program
  unit.  The directives cannot appear between program units, or at
  the beginning of internal subprograms.  They do not affect any
  modules invoked with the USE statement in the program unit that
  contains them.

  For compatibility, !MS$STRICT and !MS$NOSTRICT can be used in place
  of cDEC$ STRICT and cDEC$ NOSTRICT.

  Examples:

  Consider the following:

  ! NOSTRICT by default
  TYPE stuff
     INTEGER(4) k
     INTEGER(4) m
     CHARACTER(4) name
  END TYPE stuff
  TYPE (stuff) examp
  DOUBLE COMPLEX cd    ! non-standard data type, no error
  cd =(3.0D0, 4.0D0)
  examp.k = 4          ! non-standard component designation,
                       !   no error
  END

  SUBROUTINE STRICTDEMO( )
     !DEC$ STRICT
      TYPE stuff
        INTEGER(4) k
        INTEGER(4) m
        CHARACTER(4) name
     END TYPE stuff
     TYPE (stuff) samp
     DOUBLE COMPLEX cd      ! ERROR
     cd =(3.0D0, 4.0D0)
     samp.k = 4             ! ERROR
  END SUBROUTINE

1.1.18  –  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" is a character constant containing up to 31 printable
  characters.

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

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

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

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

  For compatibility, !MS$TITLE:  and !MS$SUBTITLE:  can be used in
  place of cDEC$ TITLE and cDEC$ SUBTITLE.

1.1.19  –  UNROLL

  cDEC$ UNROLL

  The UNROLL directive tells the compiler's optimizer how many times
  to unroll a DO loop.  It can only be applied to iterative DO loops.

  The UNROLL directive takes the following form:

  cDEC$ UNROLL [(n)]

    c    Is one of the following: C (or c), !, or *.
    n    Is an integer constant.  The range of "n" is 0 through 255.

  The UNROLL directive must precede the DO statement for each DO loop
  it affects.  No source code lines, other than the following, can be
  placed between the UNROLL directive statement and the DO statement:

   o  An IVDEP directive

   o  Placeholder lines

   o  Comment lines

   o  Blank lines

  If "n" is specified, the optimizer unrolls the loop "n" times.  If
  "n" is omitted, or if it is outside the allowed range, the
  optimizer picks the number of times to unroll the loop.

  The UNROLL directive overrides any setting of loop unrolling from
  the command line.

2  –  ACCEPT

  Transfers input data to internal storage from external records
  accessed under the sequential mode of access.  It takes one of the
  following forms:

      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.

3  –  ALLOCATABLE

  Specifies that an array is an allocatable array with a deferred
  shape.  The shape of an allocatable array is determined when an
  ALLOCATE statement is executed, dynamically allocating space for
  the array.

  The ALLOCATABLE attribute can be specified in a type declaration
  statement or an ALLOCATABLE statement, and takes one of the
  following forms:

  Type Declaration Statement:

   type, [att-ls,] ALLOCATABLE [,att-ls] :: a[(d-spec)] [,a[(d-spec)]]...

  Statement:

   ALLOCATABLE [::] a[(d-spec)] [,a[(d-spec)]]...

     type        Is a data type specifier.

     att-ls      Is an optional list of attribute specifiers.

     a           Is the name of the allocatable array; it must
                 not be a dummy argument or function result.

     d-spec      Is a deferred-shape specification (: [,:]...).
                 Each colon represents a dimension of the array.

  If the array is given the DIMENSION attribute elsewhere in the
  program, it must be declared as a deferred-shape array.

  When the allocatable array is no longer needed, it can be
  deallocated by execution of a DEALLOCATE statement.

  During program execution, the allocation status of an allocatable
  array is one of the following:

   o  Not currently allocated

      The array was never allocated or the last operation performed
      on it was a deallocation.  Deallocation is performed:

       -  Explicitly, by using a DEALLOCATE statement.

       -  By default, when the allocatable array is a local variable
          of a procedure that does not have the SAVE attribute and is
          terminated by an END or RETURN statement.

      An array that is not currently allocated must not be referenced
      or defined.

   o  Currently allocated

      The array was allocated by an ALLOCATE statement.  Such an
      array can be referenced, defined, or deallocated.

  An allocatable array cannot be specified in a COMMON, EQUIVALENCE,
  DATA, or NAMELIST statement.

  Allocatable arrays are not saved by default.  If you want to retain
  the values of an allocatable array across procedure calls, you must
  specify the SAVE attribute for the array.

  The ALLOCATABLE attribute is compatible with the AUTOMATIC,
  DIMENSION (with deferred shape), PRIVATE, PUBLIC, SAVE, STATIC,
  TARGET, and VOLATILE attributes.

  EXAMPLES:

  The following example shows a type declaration statement specifying
  the ALLOCATABLE attribute:

     REAL, ALLOCATABLE :: Z(:, :, :)

  The following is an example of the ALLOCATABLE statement:

     REAL A, B(:)
     ALLOCATABLE :: A(:,:), B

4  –  ALLOCATE

  Dynamically creates storage for allocatable arrays and pointer
  targets.  The storage space allocated is uninitialized.

  The ALLOCATE statement takes the following form:

    ALLOCATE (object [(s-spec[,s-spec...])]
              [,object[(s-spec[,s-spec...])]]...[,STAT=sv])

      object  Is the object to be allocated.  It is a variable
              name or structure component, and must be a pointer
              or allocatable array.  The object can be of type
              character with zero length.

      s-spec  Is a shape specification in the form
              [lower-bound:]upper-bound. Each bound must be a
              scalar integer expression. The number of shape
              specifications must be the same as the rank of
              the "object".

      sv      Is a scalar integer variable in which the status
              of the allocation is stored.

  A bound in "s-spec" must not be an expression containing an array
  inquiry function whose argument is any allocatable object in the
  same ALLOCATE statement; for example, the following is not
  permitted:

     INTEGER ERR
     INTEGER, ALLOCATABLE :: A(:), B(:)
     ...
     ALLOCATE(A(10:25), B(SIZE(A)), STAT=ERR)  ! A is invalid as an argu-
                                               !   ment to function SIZE

  If a STAT variable is specified, it must not be allocated in the
  ALLOCATE statement in which it appears.  If the allocation is
  successful, the variable is set to zero.  If the allocation is not
  successful, an error condition occurs, and the variable is set to a
  positive integer value (representing the run-time error).  If no
  STAT variable is specified and an error condition occurs, program
  execution terminates.

  To release the storage for an allocated array, use the DEALLOCATE
  statement.

  To determine whether an allocatable array is currently allocated,
  use the ALLOCATED intrinsic function.

  To determine whether a pointer is currently associated with a
  target, use the ASSOCIATED intrinsic function.

  For information on allocation of allocatable arrays and pointer
  targets, see the HP Fortran for OpenVMS Language Reference
  Manual.

  EXAMPLES:

  The following is an example of the ALLOCATE statement:

     INTEGER J, N, ALLOC_ERR
     REAL, ALLOCATABLE :: A(:), B(:,:)
     ...
     ALLOCATE(A(0:80), B(-3:J+1, N), STAT = ALLOC_ERR)

5  –  ASSIGN

  Assigns the value of a statement label to an integer variable.
  This feature has been deleted in Fortran 95; it was an obsolescent
  feature in Fortran 90.  VSI Fortran fully supports features
  deleted in Fortran 95.

  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.

  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 subsequent 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.

6  –  Assignment

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

     v = e

     v  Is the name of a scalar or array of intrinsic
        or derived type (with no defined assignment).
        The array cannot be an assumed-size array, and
        neither the scalar nor the array can be declared
        with the PARAMETER or INTENT(IN) attribute.

     e  Is an expression of intrinsic type or the same
        derived type as "v". Its shape must conform with
        "v". If necessary, it is converted to the same kind
        type as "v".

  Before a value is assigned to the variable, the expression part of
  the assignment statement and any expressions within the variable
  are evaluated.  No definition of expressions in the variable can
  affect or be affected by the evaluation of the expression part of
  the assignment statement.

  NOTE:  When the run-time system assigns a value to a scalar integer
  or character variable and the variable is shorter than the value
  being assigned, the assigned value may be truncated and significant
  bits (or characters) lost.  This truncation can occur without
  warning, and can cause the run-time system to pass incorrect
  information back to the program.

  If the variable is a pointer, it must be associated with a
  definable target.  The shape of the target and expression must
  conform and their types and kind type parameters must match.

6.1  –  Conversion Rules

  The following tables summarize the conversion rules for assignment
  statements.

  Table 1: Conversion Rules for Integer, Logical, or Real Expressions
  +-------------+------------------------------------------------+
  |Scalar       |  Expression (E)                                |
  |Memory       |-------------------------------------------------
  |Reference (V)|  integer, logical, or real                     |
  +-------------+------------------------------------------------+
  | integer or  |  V=INT(E)                                      |
  | logical     |                                                |
  +-------------+------------------------------------------------+
  | REAL        |  V=REAL(E)                                     |
  | (KIND=4)    |                                                |
  +-------------+------------------------------------------------+
  | REAL        |  V=DBLE(E)                                     |
  | (KIND=8)    |                                                |
  +-------------+------------------------------------------------+
  | REAL        |  V=QEXT(E)                                     |
  | (KIND=16)   |                                                |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(REAL(E), 0.0)                         |
  | (KIND=4)    |                                                |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(DBLE(E), 0.0)                         |
  | (KIND=8)    |                                                |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(QEXT(E), 0.0)                         |
  | (KIND=16)   |                                                |
  +-------------+------------------------------------------------+

  Table 2: Conversion Rules for Complex Expressions
  +-------------+------------------------------------------------+
  |Scalar       |  Expression (E)                                |
  |Memory       |-------------------------------------------------
  |Reference (V)|  complex                                       |
  +-------------+------------------------------------------------+
  | integer or  |  V=INT(REAL(E))                                |
  | logical     |  Imaginary part of E is not used.              |
  +-------------+------------------------------------------------+
  | REAL        |  V=REAL(REAL(E))                               |
  | (KIND=4)    |  Imaginary part of E is not used.              |
  +-------------+------------------------------------------------+
  | REAL        |  V=DBLE(REAL(E))                               |
  | (KIND=8)    |  Imaginary part of E is not used.              |
  +-------------+------------------------------------------------+
  | REAL        |  V=QEXT(REAL(E))                               |
  | (KIND=16)   |  Imaginary part of E is not used.              |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(REAL(REAL(E)), REAL(AIMAG(E)))        |
  | (KIND=4)    |                                                |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(DBLE(REAL(E)), DBLE(AIMAG(E)))        |
  | (KIND=8)    |                                                |
  +-------------+------------------------------------------------+
  | COMPLEX     |  V=CMPLX(QEXT(REAL(E)), QEXT(AIMAG(E)))        |
  | (KIND=16)   |                                                |
  +-------------+------------------------------------------------+

7  –  AUTOMATIC and STATIC

  Control the storage allocation of variables in subprograms.

  The AUTOMATIC and STATIC attributes can be specified in a type
  declaration statement or an AUTOMATIC or STATIC statement, and take
  one of the following forms:

  Type Declaration Statement:

    type, [att-ls,] AUTOMATIC [,att-ls] ::   v [,v]...
    type, [att-ls,] STATIC    [,att-ls] ::   v [,v]...

  Statement:

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

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     v         Is the name of a variable or an array
               specification. It can be of any type.

  AUTOMATIC and STATIC declarations only affect how data is allocated
  in storage, as follows:

   o  A variable declared as AUTOMATIC and allocated in memory
      resides in the stack storage area.

   o  A variable declared as STATIC and allocated in memory resides
      in the static storage area.

  If you want to retain definitions of variables upon reentry to
  subprograms, you must use the SAVE attribute.

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

  Automatic variables allow possible recursion.  With recursion, a
  subprogram can call itself (directly or indirectly), and resulting
  values are available upon a subsequent call or return to the
  subprogram.  For recursion to occur, RECURSIVE must be specified in
  one of the following ways:

   o  As a keyword in a FUNCTION or SUBROUTINE statement

   o  As a compiler option

   o  As an option in an OPTIONS statement

  By default, the compiler allocates local variables of non-recursive
  subprograms, except for allocatable arrays, in the static storage
  area.  The compiler may choose to allocate a variable in temporary
  (stack or register) storage if it notices that the variable is
  always defined before use.  Appropriate use of the SAVE attribute
  can prevent compiler warnings if a variable is used before it is
  defined.

  To change the default for variables, specify them as AUTOMATIC or
  specify RECURSIVE (in one of the ways mentioned above).

  To override any compiler option that may affect variables,
  explicitly specify the variables as AUTOMATIC or STATIC.

                                 NOTE

          Variables that are data-initialized, and  variables
          in  COMMON  and  SAVE statements are always static.
          This is regardless of  whether  a  compiler  option
          specifies recursion.

  A variable cannot be specified as AUTOMATIC or STATIC more than
  once in the same scoping unit.

  If the variable is a pointer, AUTOMATIC or STATIC apply only to the
  pointer itself, not to any associated target.

  Some variables cannot be specified as AUTOMATIC or STATIC.  The
  following table shows these restrictions:

  Variable                    AUTOMATIC       STATIC
  --------                    ---------       ------
  Dummy argument                No              No
  Automatic object              No              No
  Common block item             No              Yes
  Use-associated item           No              No
  Function result               No              No
  Component of a derived type   No              No

  A variable can be specified with both the STATIC and SAVE
  attributes.

  If a variable is in a module's outer scope, it can be specified as
  STATIC, but not as AUTOMATIC.

  The AUTOMATIC attribute is compatible with the ALLOCATABLE,
  DIMENSION, POINTER, TARGET, and VOLATILE attributes.

  The STATIC attribute is compatible with the ALLOCATABLE, DIMENSION,
  POINTER, PRIVATE, PUBLIC, SAVE, TARGET, and VOLATILE attributes.

8  –  BACKSPACE

  Positions a sequential file at the beginning of the preceding
  record, making it available for subsequent I/O processing.  The
  file must be on disk or tape.  Statement format:

      BACKSPACE ([UNIT=]io-unit [,ERR=label] [,IOSTAT=i-var])
      BACKSPACE io-unit

      io-unit  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.

      label    Is the label of a statement that receives control
               if an error occurs, prefaced by ERR=.

      i-var    Is a scalar 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, append, or keyed access, because record "n" is not
  available to the RMS I/O system.

  If a file is already positioned at the beginning of a file, a
  BACKSPACE statement has no effect.

9  –  BLOCK_DATA

  Begins a block data program unit.  Statement format:

     BLOCK DATA [nam]
       [stmts]
     END [BLOCK DATA [nam]]

     nam   Is the symbolic name used to identify the block.

     stmts Is one or more of the following statements:

            COMMON        PARAMETER  Type declaration
            DATA          POINTER    Derived-type definition
            DIMENSION     RECORD     Record structure declaration
            EQUIVALENCE   SAVE
            IMPLICIT      TARGET
            INTRINSIC     USE

     Note: A type declaration cannot contain the ALLOCATABLE,
           EXTERNAL, INTENT, OPTIONAL, PRIVATE, or PUBLIC
           attributes.

  A BLOCK DATA statement and its associated specification statements
  are a special kind of program unit, called a block data subprogram.

  A block data program unit need not be named, but there can only be
  one unnamed block data program unit in an executable program.

  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.  If a name follows the
  END statement, it must be the same as the name specified in the
  BLOCK DATA 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 specification statements that establishes the common block.
  However, all of 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.

10  –  CALL

  Transfers control and passes arguments to a subprogram.  Statement
  format:

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

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

     a    Is an actual argument optionally preceded by [keyword=],
          where "keyword" is the name of a dummy argument in the
          explicit interface for the subroutine.  The keyword is
          assigned a value when the  procedure is invoked.

  Each actual argument must be a variable, an expression, the name of
  a procedure, or an alternate return specifier.  (It must not be the
  name of an internal procedure, statement function, or the generic
  name of a procedure.)

  An alternate return specifier is an asterisk (*) or ampersand (&)
  followed by the label of an executable branch target statement in
  the same scoping unit as the CALL statement.

                                 NOTE

          An alternate return is an  obsolescent  feature  in
          Fortran  95  and  Fortran 90.  VSI Fortran fully
          supports this feature.

  When the CALL statement is executed, any expressions in the actual
  argument list are evaluated, then control is passed to the first
  executable statement or construct in the subroutine.  When the
  subroutine finishes executing, control returns to the next
  executable statement following the CALL statement, or to a
  statement identified by an alternate return label (if any).

  If an argument list appears, each actual argument is associated
  with the corresponding dummy argument by its position in the
  argument list or by the name of its keyword.  The arguments must
  agree in type and kind type parameters.

  If positional arguments and argument keywords are specified, the
  argument keywords must appear last in the actual argument list.

  If a dummy argument is optional, the actual argument can be
  omitted.

  An actual argument associated with a dummy procedure must be the
  specific name of a procedure, or be another dummy procedure.
  Certain specific intrinsic function names must not be used as
  actual arguments. (See the HP Fortran for OpenVMS Language
  Reference Manual.)

  You can use a CALL statement to invoke a function as long as the
  function is not one of the following types:

   o  REAL(8)

   o  REAL(16)

   o  COMPLEX(8)

   o  COMPLEX(16)

   o  CHARACTER

  EXAMPLES:

  The following example shows a subroutine with argument keywords:

    PROGRAM KEYWORD_EXAMPLE
      INTERFACE
        SUBROUTINE TEST_C(I, L, J, KYWD2, D, F, KYWD1)
        INTEGER I, L(20), J, KYWD1
        REAL, OPTIONAL :: D, F
        COMPLEX KYWD2
        ...
        END SUBROUTINE TEST_C
      END INTERFACE
      INTEGER I, J, K
      INTEGER L(20)
      COMPLEX Z1
      CALL TEST_C(I, L, J, KYWD1 = K, KYWD2 = Z1)
      ...

  The first three actual arguments are associated with their
  corresponding dummy arguments by position.  The argument keywords
  are associated by keyword name, so they can appear in any order.

  Note that the interface to subroutine TEST has two optional
  arguments that have been omitted in the CALL statement.

11  –  CASE

  Conditionally executes one block of constructs or statements
  depending on the value of a scalar expression in a SELECT CASE
  statement.  Statement format:

    [name :] SELECT CASE (expr)
    [CASE (case-value [,case-value]...) [name]
      block]...
    [CASE DEFAULT [name]
      block]
    END SELECT [name]

    name   Is the name of the CASE construct.

    expr   Is an expression of type integer, logical, or
           character (enclosed in parentheses). Evaluation
           of this expression results in a value called
           the case index.

    case-value  Is one or more compile-time constant expressions
                of type integer, logical, or character (enclosed
                in parentheses).  Each "case-value" must be of the
                same data type as "expr". If the type is character,
                "case-value" and "expr" can be of different lengths.

                Integer and character expressions can be expressed
                as a range of case values, taking one of the following
                forms:

                low:high
                low:
                :high

                Case values must not overlap.

    block  Is a sequence of zero or more statements or
           constructs.

  If a construct name is specified in a SELECT CASE statement, the
  same name must appear in the corresponding END SELECT statement.
  The same construct name can optionally appear in any CASE statement
  in the construct.

  The case expression ("expr") is evaluated first.  The resulting
  case index is compared to the case values to find a matching value
  (there can only be one).  When a match occurs, the block following
  the matching case value is executed and the construct terminates.

  The following rules determine whether a match occurs:

   o  When the case value is a single value (no colon appears), a
      match occurs as follows:

        Data Type              A Match Occurs If:
        ---------              ---------------------------
        Logical                case-index .EQV. case-value
        Integer or character   case-index ==  case-value

   o  When the case value is a range of values (a colon appears), a
      match depends on the range specified, as follows:

        Range       A Match Occurs If:
        -----       -------------------------
        low:        case-index >= low
        :high       case-index <= high
        low:high    low <= case-index <= high

  The following are all valid case values:

     CASE (1, 4, 7, 11:14, 22)      ! Individual values as specified:
                                    !     1, 4, 7, 11, 12, 13, 14, 22
     CASE (:-1)                     ! All values less than zero
     CASE (0)                       ! Only zero
     CASE (1:)                      ! All values above zero

  If no match occurs but a CASE DEFAULT statement is present, the
  block following that statement is executed and the construct
  terminates.

  If no match occurs and no CASE DEFAULT statement is present, no
  block is executed, the construct terminates, and control passes to
  the next executable statement or construct following the END SELECT
  statement.

  The following are examples of CASE constructs:

    INTEGER FUNCTION STATUS_CODE (I)
      INTEGER I
      CHECK_STATUS: SELECT CASE (I)
      CASE (:-1)
        STATUS_CODE = -1
      CASE (0)
        STATUS_CODE = 0
      CASE (1:)
        STATUS_CODE = 1
      END SELECT CHECK_STATUS
    END FUNCTION STATUS_CODE

    SELECT CASE (J)
    CASE (1, 3:7, 9)    ! Values: 1, 3, 4, 5, 6, 7, 9
      CALL SUB_A
    CASE DEFAULT
      CALL SUB_B
    END SELECT

  The following three examples are equivalent:

    1. SELECT CASE (ITEST .EQ. 1)
       CASE (.TRUE.)
         CALL SUB1 ()
       CASE (.FALSE.)
         CALL SUB2 ()
       END SELECT

    2. SELECT CASE (ITEST)
       CASE DEFAULT
         CALL SUB2 ()
       CASE (1)
         CALL SUB1 ()
       END SELECT

    3. IF (ITEST .EQ. 1) THEN
         CALL SUB1 ()
       ELSE
         CALL SUB2 ()
       END IF

12  –  CLOSE

  Closes a file.  Statement format:

     CLOSE ([UNIT=]io-unit[,p][,ERR=label][,IOSTAT=i-var])

     io-unit 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 (unless OPEN(READONLY)
                                is specified).
                               *DEFAULT FOR SCRATCH FILES*
             'PRINT'            Submits the file as a print job.
             'PRINT/DELETE'     Submits the file as a print job,
                                then deletes it.
             'SUBMIT'           Submits the file as a batch job.
             'SUBMIT/DELETE'    Submits the file as a batch job,
                                then deletes it.

      label  Is the label of an executable statement that
             receives control if an error occurs.

      i-var  Is a scalar integer variable. (Returns a
             zero if no error condition exists or a positive
             integer if an error condition exists.)

  The CLOSE statement specifiers can appear in any order.  An I/O
  unit must be specified, but the UNIT specifier is optional if the
  unit specifier is the first item in the I/O control list.

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

  If a CLOSE statement is specified for a unit that is not open, it
  has no effect.

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;
  subsequent 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 that identifies the common block.

     nlist  Is one or more names of variables that identify items in
            the common block. The variable must not be a dummy
            argument, allocatable array, automatic object, function,
            function result, or entry to a procedure.

            It must not have the PARAMETER attribute.  If an object
            of derived type is specified, it must be a sequence type.

  A common block is a global entity, and must not have the same name
  as any other global entity in the program, such as a subroutine or
  function.

  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.

  A variable can appear in only one common block within a scoping
  unit.

  If an array is specified, it can be followed by an explicit-shape
  array specification.  The array must not have the POINTER attribute
  and each bound in the specification must be a constant
  specification expression.

  A pointer can only be associated with pointers of the same type,
  kind type parameters, and rank.

  Nonpointer variables can be associated if they are of different
  numeric type.

  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.

  Named common blocks must be declared to have the same size in each
  program unit.  Blank common can have different lengths in different
  program units.

14  –  CONTAINS

  Separates the body of a main program, module, or external
  subprogram from any internal or module procedures it may contain.
  It is not executable.  Statement format:

     CONTAINS

15  –  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

  The statement by itself does nothing and has no effect on program
  results or execution sequence.

16  –  CYCLE

  Terminates the current execution cycle of the innermost (or named)
  DO construct.  Statement format:

     CYCLE [name]

     name   Is the name of the DO construct.

  When a CYCLE statement is executed, the following occurs:

  1.  The current execution cycle of the named (or innermost) DO
      construct is terminated.

      If a DO construct name is specified, the CYCLE statement must
      be within the range of that construct.

  2.  The iteration count (if any) is decremented by 1.

  3.  The DO variable (if any) is incremented by the value of the
      increment parameter (if any).

  4.  A new iteration cycle of the DO construct begins.

  Any executable statements following the CYCLE statement (including
  a labeled terminal statement) are not executed.

  A CYCLE statement can be labeled, but it cannot be used to
  terminate a DO construct.

  The following example shows the CYCLE statement:

  DO I =1, 10
    A(I) = C + D(I)
    IF (D(I) < 0) CYCLE    ! If true, the next statement is omitted
    A(I) = 0               ! from the loop and the loop is tested again.
  END DO

17  –  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 variables
            and implied-DO lists, separated by commas.  RECORD
            structures are not allowed in this list.

            Subscript expressions and expressions in substring
            references must be initialization expressions.

            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 elements,
                      character substrings, scalar structure
                      components or implied-DO lists, separated
                      by commas.

            i         Is the name of a scalar integer variable.

            n1,n2,n3  Are scalar integer 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.

  The following objects cannot be initialized in a DATA statement:

   o  A dummy argument

   o  A function

   o  A function result

   o  An automatic object

   o  An allocatable array

   o  A variable that is accessible by use or host association

   o  A variable in a named common block (unless the DATA statement
      is in a block data program unit)

   o  A variable in blank common

  For details, see the HP Fortran for OpenVMS Language Reference
  Manual.

18  –  DEALLOCATE

  Frees storage allocated for allocatable arrays and pointer targets.
  It takes the following form:

    DEALLOCATE (object [,object]...[,STAT=sv])

      object  Is a structure component or the name of a variable,
              and must be a pointer or allocatable array.

      sv      Is a scalar integer variable in which the status
              of the deallocation is stored.

  If a STAT variable is specified, it must not be deallocated in the
  DEALLOCATE statement in which it appears.  If the deallocation is
  successful, the variable is set to zero.  If the deallocation is
  not successful, an error condition occurs, and the variable is set
  to a positive integer value (representing the run-time error).  If
  no STAT variable is specified and an error condition occurs,
  program execution terminates.

  It is recommended that all explicitly allocated storage be
  explicitly deallocated when it is no longer needed.

  For information on deallocation of allocatable arrays and pointer
  targets, see the HP Fortran for OpenVMS Language Reference Manual.

  EXAMPLES:

  The following is an example of the DEALLOCATE statement:

     INTEGER ALLOC_ERR
     REAL, ALLOCATABLE :: A(:), B(:,:)
     ...
     ALLOCATE (A(10), B(-2:8,1:5))
     ...
     DEALLOCATE(A, B, STAT = ALLOC_ERR)

19  –  DECODE

  See COMPATIBILITY_FEATURES in this Help file.

20  –  DEFINE_FILE

  See COMPATIBILITY_FEATURES in this Help file.

21  –  DELETE

  Deletes a record from an indexed or a relative file.  Statement
  format:

  Format -- Indexed:

     DELETE ([UNIT=]io-unit [,ERR=label] [,IOSTAT=i-var])

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

  Format -- Relative:

     DELETE ([UNIT=]io-unit [,REC=r] [,ERR=label] [,IOSTAT=i-var])
     DELETE (io-unit'r [,ERR=label] [,IOSTAT=i-var])

     Deletes the specified record from a relative file.

     io-unit   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=.

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

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

     i-var     Is an I/O status specifier, prefaced by IOSTAT=.
               (Returns a zero if no error condition exists or
               a positive integer if an error condition exists.)

  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.

  If REC=r is omitted, the current record is deleted.  When the
  direct access record is deleted, any associated variable is set to
  the next record number.

22  –  DIMENSION

  Specifies that an object is an array, and defines the shape of the
  array.

  The DIMENSION attribute can be specified in a type declaration
  statement or a DIMENSION statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] DIMENSION (spec) [,att-ls] :: a[(spec)] [,a[(spec)]]...

  Statement:

   DIMENSION [::] a(spec) [,a(spec)]...

     type        Is a data type specifier.

     att-ls      Is an optional list of attribute specifiers.

     spec        Is an array specification.  In a type declaration,
                 any array specification following an array overrides
                 any array specification following DIMENSION.

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

  An array can also be declared in the following statements:
  ALLOCATABLE, POINTER, TARGET, and COMMON.

  The DIMENSION attribute is compatible with the ALLOCATABLE,
  AUTOMATIC, INTENT, OPTIONAL, POINTER, PRIVATE, PUBLIC, SAVE,
  STATIC, TARGET, and VOLATILE attributes.

  See also DATA ARRAYS in this Help file.

23  –  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
  (indexed DO).  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:

      [name:] DO [s][,] v = e1,e2[,e3]
         block
      [s] term-stmt

      name Is the name of the DO construct.

      s    Is an optional label of an executable statement
           which 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.

      block Is a sequence of zero or more statements or
            constructs.

      term-stmt Is the terminal statement for the construct.

  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.

  If a DO statement does not contain a terminal statement label, the
  construct must be terminated by an END DO statement.  If it does
  contain a terminal statement label, the END DO is optional.

  If a construct name is specified in a block DO statement, the same
  name must appear in the terminal END DO statement.  If no construct
  name is specified in the block DO statement, no name can appear in
  the terminal END DO statement.  The construct name must be a unique
  identifier in the program unit.

  The following cannot be terminal statements for DO constructs:
  CYCLE, DO, END (for a program unit), EXIT, GO TO, IF, RETURN, or
  STOP.

24  –  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 which 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.

25  –  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

26  –  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.

27  –  ELSEWHERE

  An optional statement in a WHERE construct.  Statement format:

     ELSEWHERE (mask-expr2) [name]
     or
     ELSEWHERE [name]

  The "mask-expr2" is a logical array expression (called a mask
  expression).

  The "name" is the name of the WHERE construct.

  Assignment statements following an ELSEWHERE statement are executed
  as if they were WHERE statements with ".NOT.  where-mask-expr".  If
  ELSEWHERE specifies "mask-expr2", it is executed as "(.NOT.
  where-mask-expr) .AND.  mask-expr2".

  See also STATEMENTS WHERE in this Help file.

28  –  ENCODE

  See COMPATIBILITY_FEATURES in this Help file.

29  –  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

30  –  END_DO

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

     END DO

31  –  END_IF

  Terminates a block IF construct.  Statement format:

     END IF

32  –  END_MAP

  Marks the end of a map declaration within a union declaration in a
  record 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

33  –  END_SELECT

  Marks the end of a CASE construct.  Statement format:

     END SELECT [name]

34  –  END_STRUCTURE

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

     END STRUCTURE

35  –  END_TYPE

  Marks the end of a derived-type definition.  The END statement must
  be present as the last statement of every derived-type definition.
  Statement format:

     END TYPE

  For more information on derived types, see DATA DERIVED_TYPES in
  this Help file.

36  –  END_UNION

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

     END UNION

37  –  ENDFILE

  For sequential files, writes an end-of-file record to the file and
  positions the file after this record (the terminal point).  For
  direct access files, truncates the file after the current record.

  Statement format:

     ENDFILE ([UNIT=]io-unit[,ERR=label][,IOSTAT=i-var])
     ENDFILE io-unit

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

     label     Is the label of an executable statement that
               receives control if an error occurs, prefaced
               by ERR=.

     i-var     Is an I/O status specifier, prefaced by IOSTAT=.
               (Returns a zero if no error condition exists or
               a positive integer if an error condition exists.)

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

  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
  performed on a direct access file always truncates the file.

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

38  –  ENTRY

  Designates an alternate entry point at which execution of a
  subprogram can start.  It is not executable and must precede any
  CONTAINS statement (if any) within the subprogram.  Statement
  format:

     ENTRY nam [([p[,p]...])] [RESULT (r-name)]]

     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: Type default integer, default real, double
                      precision real, default complex, double complex,
                      or default logical
             Group 2: REAL(KIND=16) and COMPLEX(KIND=16)
             Group 3: Type default character

             If the data type is character, the length of the string
             must be the same in both the entry and the function.

     p       Is a dummy argument or an alternate return argument
             (designated by a *).  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.

     r-name  Is the name of a function result.  This name must not be
             the same as the name of the entry point, or the name of
             any other function or function result.  This parameter
             can only be specified for function subprograms.

  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.

  An ENTRY statement must not appear in a CASE, DO, IF, FORALL, or
  WHERE construct or a nonblock DO loop.

39  –  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.

  The following objects cannot be specified in EQUIVALENCE
  statements:

   o  A dummy argument

   o  An allocatable array

   o  A pointer

   o  An object of nonsequence derived type

   o  An object of sequence derived type containing a pointer in the
      structure

   o  A function, entry, or result name

   o  A named constant

   o  A structure component

   o  A subobject of any of the above objects

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

40  –  EXIT

  The EXIT statement terminates execution of a DO construct.
  Statement format:

     EXIT [name]

     name  Is the name of the DO construct.

  The EXIT statement causes execution of the named (or innermost) DO
  construct to be terminated.

  If a DO construct name is specified, the EXIT statement must be
  within the range of that construct.

  Any DO variable present retains its last defined value.

  An EXIT statement can be labeled, but it cannot be used to
  terminate a DO construct.

  The following example shows an EXIT statement:

  LOOP_A : DO I = 1, 15
    N = N + 1
    IF (N > I) EXIT LOOP_A
  END DO LOOP_A

41  –  EXTERNAL

  Allows an external or dummy procedure to be used as an actual
  argument.  (To specify intrinsic procedures as actual arguments,
  use the INTRINSIC statement.)

  The EXTERNAL attribute can be specified in a type declaration
  statement or an EXTERNAL statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type [att-ls,] EXTERNAL [,att-ls] :: v[,v]...

  Statement:

   EXTERNAL v [,v]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     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 object.

  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.

  The EXTERNAL attribute is compatible with the OPTIONAL, PRIVATE,
  and PUBLIC attributes.

42  –  FIND

  See COMPATIBILITY_FEATURES in this Help file.

43  –  FORALL

  A generalization of the Fortran 95/90 WHERE statement and
  construct.  It allows more general array shapes to be assigned,
  especially in construct form.  Statement format:

    FORALL (triplet-spec [,triplet-spec]...[,mask-expr]) assign-stmt

  Construct format:

    [name: ] FORALL (triplet-spec [,triplet-spec]...[,mask-expr])
    forall-body-stmt
    [forall-body-stmt]...
    END FORALL [name]

    name          Is the name of the FORALL construct.

    triplet-spec  Is a triplet specification with the following form:

      subscript-name = subscript-1 : subscript-2 [:stride]

      The "subscript-name" must be a scalar of type integer.
      It is valid only within the scope of the FORALL; its
      value is undefined on completion of the FORALL.

      The "subscript"s and "stride" cannot contain a reference
      to any "subscript-name" in "triplet-spec".

      The "stride" cannot be zero.  If it is omitted, the default
      value is 1.

      Evaluation of an expression in a triplet specification must
      not affect the result of evaluating any other expression in
      another triplet specification.

    mask-expr  Is a logical array expression (called the mask
               expression). If it is omitted, the value .TRUE.
               is assumed. The mask expression can reference the
               subscript name in "triplet-spec".

    assign-stmt  Is an assignment statement or a pointer assignment
                 statement. The variable being assigned to must be
                 an array element or array section and must reference
                 all subscript names included in all "triplet-spec"s.

    forall-body-stmt  Is one of the following:
                      o An "assign-stmt"
                      o A WHERE statement or construct
                        The WHERE statement or construct uses a mask
                        to make array assignments.
                      o A FORALL statement or construct

  If a construct name is specified in the FORALL statement, the same
  name must appear in the corresponding END FORALL statement.

  A FORALL statement is executed by first evaluating all bounds and
  stride expressions in the triplet specifications, giving a set of
  values for each subscript name.  The FORALL assignment statement is
  executed for all combinations of subscript name values for which
  the mask expression is true.

  The FORALL assignment statement is executed as if all expressions
  (on both sides of the assignment) are completely evaluated before
  any part of the left side is changed.  Valid values are assigned to
  corresponding elements of the array being assigned to.  No element
  of an array can be assigned a value more than once.

  A FORALL construct is executed as if it were multiple FORALL
  statements, with the same triplet specifications and mask
  expressions.  Each statement in the FORALL body is executed
  completely before execution begins on the next FORALL body
  statement.

  Any procedure referenced in the mask expression or FORALL
  assignment statement must be pure.

  Pure functions can be used in the mask expression or called
  directly in a FORALL statement.  Pure subroutines cannot be called
  directly in a FORALL statement, but can be called from other pure
  procedures.

  EXAMPLES:

  Consider the following:

    FORALL(I = 1:N, J = 1:N, A(I, J) .NE. 0.0) B(I, J) = 1.0 / A(I, J)

  This statement takes the reciprocal of each nonzero element of
  array A(1:N, 1:N) and assigns it to the corresponding element of
  array B.  Elements of A that are zero do not have their reciprocal
  taken, and no assignments are made to corresponding elements of B.

  Every array assignment statement and WHERE statement can be written
  as a FORALL statement, but some FORALL statements cannot be written
  using just array syntax.  For example, the preceding FORALL
  statement is equivalent to the following:

    WHERE(A /= 0.0) B = 1.0 / A

  It is also equivalent to:

    FORALL (I = 1:N, J = 1:N)
      WHERE(A(I, J) .NE. 0.0) B(I, J) = 1.0/A(I, J)
    END FORALL

  However, the following FORALL example cannot be written using just
  array syntax:

     FORALL(I = 1:N, J = 1:N) H(I, J) = 1.0/REAL(I + J - 1)

  This statement sets array element H(I, J) to the value 1.0/REAL(I +
  J - 1) for values of I and J between 1 and N.

  Consider the following:

    TYPE MONARCH
      INTEGER, POINTER :: P
    END TYPE MONARCH

    TYPE(MONARCH), DIMENSION(8)   :: PATTERN
    INTEGER, DIMENSION(8), TARGET :: OBJECT
    FORALL(J=1:8)  PATTERN(J)%P => OBJECT(1+IEOR(J-1,2))

  This FORALL statement causes elements 1 through 8 of array PATTERN
  to point to elements 3, 4, 1, 2, 7, 8, 5, and 6, respectively, of
  OBJECT.  IEOR can be referenced here because it is pure.

  The following example shows a FORALL construct:

    FORALL(I = 3:N + 1, J = 3:N + 1)
      C(I, J) = C(I, J + 2) + C(I, J - 2) + C(I + 2, J) + C(I - 2, J)
      D(I, J) = C(I, J)
    END FORALL

  The assignment to array D uses the values of C computed in the
  first statement in the construct, not the values before the
  construct began execution.

  FORALL is a language feature of Fortran 95.

44  –  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 data edit (field) descriptor, a control edit
          descriptor, a string edit descriptor, or a group of
          such 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 "data edit descriptor" has one of the following forms:

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

     r    Is an 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,EN,ES,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 ranges for "r", "w", "m", "d", and "e" are as follows:

  Term      Range
  ----      __________
   r        1 to 2147483647 (2**31-1)
   w        1 to 2147483647
   m        0 to 32767 (2**15-1)
   d        0 to 32767
   e        1 to 32767

  The terms 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.

  You cannot use PARAMETER constants for "r", "w", "m", "d", or "e".

  The "control 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,
           Q, $, or :).

     n     Is an 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 2147483647 (2**31-1); actual useful ranges may be
  constrained by record sizes (RECL) and the file system.

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

     "string" 'string'  nHc1...cn

     string  Is a character literal constant.

     n       Is the number of characters to be transferred.

     c1...cn Is a string of printable ASCII characters.

  Although no string edit descriptor can be preceded by a repeat
  specification, a parenthesized group of string edit descriptors can
  be preceded by a repeat specification.

  For more information, see FORMAT_SPECIFIERS in this Help file.

45  –  FUNCTION

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

     [prefx] FUNCTION nam [([p[,p]...])] [RESULT (r-nam)]

     prefx Is either:

           typ [kywd]
           kywd [typ]

     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 an assumed-length function
           type -- the function type assumes the length of its
           definition in the program unit invoking it. Assumed-
           length character functions are obsolescent in
           Fortran 95.  VSI Fortran flags obsolescent features,
           but fully supports them.

     kywd  Is one of the following:

           RECURSIVE    Permits direct recursion to occur.  If
                        a function is directly recursive and
                        array valued, RESULT must also be
                        specified.

           PURE         Restricts the procedure from having
                        side effects.

           ELEMENTAL    Specifies PURE with certain constraints:

                        o A dummy argument:
                          - Must be scalar and cannot have the POINTER
                            attribute
                          - Cannot appear in a specification expression,
                            except as an argument to the BIT_SIZE, KIND,
                            or LEN intrinsic functions or the numeric
                            inquiry intrinsic functions
                          - Must not be *
                          - Must not be a dummy procedure

                        o The function result must be scalar and cannot
                          have the POINTER attribute.

                        An explicit interface must be visible to the
                        caller of an ELEMENTAL procedure.

                        If ELEMENTAL is specified, RECURSIVE must not
                        be specified.

     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.

           The name can be followed by * and 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.  This length specification is not
           permitted if the length has already been specified
           following CHARACTER.

     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.

     r-nam Is the name of the function result.  This name must not
           be the same as the function name.

  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.

45.1  –  RESULT Keyword

  Specifies a name for the result variable of a function.  Its name
  must be different from the name of the function.

  If RESULT is not specified, the function name is the result
  variable.  All references to the function are references to the
  function result variable.

  If RESULT is specified, the result name is the result variable.
  In this case, all references to the function name are recursive
  calls, and the function name must not appear in specification
  statements.

  The following is an example of a recursive function specifying a
  RESULT variable:

    RECURSIVE FUNCTION FACTORIAL(P) RESULT(L)
      INTEGER, INTENT(IN) :: P
      INTEGER L
      IF (P == 1) THEN
        L = 1
      ELSE
        L = P * FACTORIAL(P - 1)
      END IF
    END FUNCTION

45.2  –  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 cannot specify more than 255 arguments.

46  –  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.

46.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.

46.2  –  Computed

  Transfers control to a statement based upon the value of an
  expression within the statement.  This is an obsolescent feature in
  Fortrsn 95.  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.

                                 NOTE

          This  statement  is  obsolescent  in  Fortran   95.
          HP  Fortran  flags  obsolescent  features,  but
          fully supports them.

46.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.

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

  This feature has been deleted in Fortran 95; it was an obsolescent
  feature in Fortran 90.  VSI Fortran fully supports features
  deleted in Fortran 95.

47  –  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.

47.1  –  Arithmetic

  Conditionally transfers control to one of three statements, based
  on the current value of an arithmetic expression.  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.

                                 NOTE

          The  arithmetic  IF  statement  is  an  obsolescent
          feature  in  Fortran  95  and  Fortran  90.  HP
          Fortran fully supports this feature.

47.2  –  Logical

  Executes the statement if the logical expression is true.  In
  Fortran 95/90, this is called an IF statement (as compared to block
  IFs, which are called IF constructs).  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,
         CASE, FORALL, or WHERE constructs, or another logical
         IF statement.

47.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:

     [name:] IF (e) THEN
       block
     [ELSE IF (e1) THEN [name]
       block]...
     [ELSE [name]
       block]
     END IF [name]

     name   Is the name of the IF construct.

     e,e1   Are logical expressions.

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

  If a construct name is specified in a block IF statement, the same
  name must appear in the terminal END IF statement.  If no construct
  name is specified in the block IF statement, no name can appear in
  the terminal END IF statement.  The construct name must be a unique
  identifier in the program unit.

                                 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

48  –  IMPLICIT

  Overrides implied (default) data typing of symbolic names.
  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.  The largest valid value of len
          on Tru64 UNIX and Linux is 2147483647 (2**31-1); on OpenVMS
          the largest valid value is 65535.  Negative values are
          treated as zero.

     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.

  Names beginning with a dollar sign ($) are implicitly INTEGER.
  This implicit type cannot be changed in an IMPLICIT statement.

49  –  IMPLICIT_NONE

  Disables 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 diagnostic messages when  variables  are
          used   but   not  declared,  you  can  specify  the
          /WARNINGS=DECLARATIONS compiler option  instead  of
          IMPLICIT NONE.

50  –  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 the HP Fortran for OpenVMS 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.

                     On Tru64 UNIX and Linux systems, you can only
                     use /[NO]LIST if you specify the compiler
                     option that sets OpenVMS defaults.

     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 the
                     HP Fortran for OpenVMS User Manual.

     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 contain any alphanumeric
                     character and the special characters dollar
                     sign ($) and underscore (_).  Its length
                     must be acceptable to the operating system,
                     as described in the HP Fortran for OpenVMS User
                     Manual.

  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 when system resources are exhausted.

  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

51  –  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 may 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

51.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[,ADVANCE=exp][,SIZE=var][,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[,ADVANCE=exp][,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]

51.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 subsequently 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]

51.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]

51.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])

  Comments (beginning with !  only) can appear anywhere in namelist
  input.  The comment extends to the end of the source line.

52  –  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:

   Inquiring by File:

     INQUIRE (FILE=fi [,ERR=lbl][,IOSTAT=ivar][,DEFAULTFILE=def], flist)

   Inquiring by Unit:

     INQUIRE ([UNIT=]u [,ERR=lbl][,IOSTAT=ivar], flist)

   Inquiring by Output List:

     INQUIRE (IOLENGTH=len) olist

     fi     Is a scalar default character expression
            specifying the name of the file for inquiry.

     lbl    Is the label of the branch target statement
            that receives control if an error occurs.

     var    Is a scalar integer variable that is defined
            as a positive integer if an error occurs and
            zero if no error occurs.

     def    Is a scalar default character expression specifying
            a default file pathname (or file specification) string.

     flist  Is one or more inquiry specifiers. Each specifier
            can appear 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.

     len    Is a scalar integer variable indicating
            the number of bytes of data that would result from
            using "olist" in an unformatted output statement.

     olist  Is a list of one or more output items.

  FILE=fi, UNIT=u, ERR=lbl, and IOSTAT=var can appear anywhere within
  the parentheses following INQUIRE.  However, if the UNIT keyword is
  omitted, the unit specifier ("u") must be the first parameter in
  the list.

  An INQUIRE statement may 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.

  To get file characteristics, specify the INQUIRE statement after
  opening the file.  (File characteristics are stored in the file
  header.)

52.1  –  ACCESS

  ACCESS = acc

  acc  Is a scalar default character variable 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
  'UNDEFINED'       If the file is not open

52.2  –  ACTION

  ACTION = act

  act  Is a scalar default character variable that is assigned
       one of the following values:

  'READ'       If the file is connected for input only
  'WRITE'      If the file is connected for output only
  'READWRITE'  If the file is connected for both input
               and output
  'UNDEFINED'  If the file is not connected

52.3  –  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.)

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

52.4  –  BLOCKSIZE

  BLOCKSIZE = bks

  bks  Is a scalar integer variable.

  The "bks" is assigned the current size of the I/O buffer.  If the
  unit or file is not connected, the value assigned is zero.

52.5  –  BUFFERED

  BUFFERED = bf

  bf   Is a scalar default character variable that is assigned
       one of the following values:

       'NO'         If the file or unit is connected and
                    buffering is not in effect.

       'YES'        If the file or unit is connected and
                    buffering is in effect.

       'UNKNOWN'    If the file or unit is not connected.

52.6  –  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 the file is not open

52.7  –  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.

  'FDX':            If the file is open with little endian
                    integer and VAX F_floating, D_floating,
                    and IEEE X_floating data conversion in
                    effect.

  'FGX':            If the file is open with little endian
                    integer and VAX F_floating, G_floating,
                    and IEEE X_floating 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 VAX F_floating, D_floating,
                    and H_floating data conversion in effect.

  'VAXG':           If the file is open with little endian
                    integer and VAX F_floating, G_floating,
                    and H_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.

52.8  –  DELIM

  DELIM = del

  del  Is a scalar default character variable that is assigned
       one of the following values:

  'APOSTROPHE'  If apostrophes are used to delimit character
                constants in list-directed and namelist output

  'QUOTE'       If quotation marks are used to delimit character
                constants in list-directed and namelist output

  'NONE'        If no delimiters are used

  'UNDEFINED'   If the file is not connected, or is not connected
                for formatted data transfer

52.9  –  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 file is not open

52.10  –  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".

52.11  –  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.

52.12  –  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
  'UNDEFINED'       If the file is not open

52.13  –  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

52.14  –  IOSTAT

  IOSTAT = ios

  ios  Is a scalar default integer variable.

  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.

52.15  –  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

52.16  –  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.

52.17  –  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

52.18  –  NEXTREC

  NEXTREC = nr

  nr  Is a scalar integer variable that is assigned
      a value as follows:

      - If the file is connected for direct access and a
        record (r) was previously read or written, the value
        assigned is r + 1.

      - If no record has been read or written, the value
        assigned is 1.

      - If the file is not connected for direct access, or
        if the file position cannot be determined because
        of an error condition, the value assigned is zero.

      - If the file is connected for direct access and a REWIND
        has been performed on the file, the value assigned is 1.

52.19  –  NUMBER

  NUMBER = num

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

52.20  –  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

52.21  –  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'            If the file is an indexed file
  'UNKNOWN'            If the file organization cannot
                        be determined

52.22  –  PAD

  PAD = pd

  pd   Is a scalar default character variable that is assigned
       one of the following values:

  'NO'   If the file or unit was connected with PAD='NO'

  'YES'  If the file or unit was connected with PAD='YES'

52.23  –  POSITION

  POSITION = pos

  pos   Is a scalar default character variable that is assigned
        one of the following values:

  'REWIND'    If  the file is connected with its position
              at its initial point

  'APPEND'    If the file is connected with its position
              at its terminal point (or before its end-of-file
              record, if any)

  'ASIS'      If the file is connected without changing
              its position

  'UNDEFINED' If the file is not connected, or is connected
              for direct access data transfer and a REWIND
              statement has not been performed on the unit.

52.24  –  READ

  READ = rd

  rd   Is a scalar default character variable that is assigned
       one of the following values:

  'YES'     If the file can be read

  'NO'      If the file cannot be read

  'UNKNOWN' If the processor cannot determine whether
            the file can be read

52.25  –  READWRITE

  READWRITE = rdwr

  rdwr   Is a scalar default character variable that is assigned
         one of the following values:

  'YES'     If the file can be both read and written to

  'NO'      If the file cannot be both read and written to

  'UNKNOWN' If the processor cannot determine whether
            the file can be both read and written to

52.26  –  RECL

  RECL = rcl

  rcl  Is a scalar integer variable 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 assigned value is expressed in longwords (4-byte units) if the
  file is currently (or was previously) connected for unformatted
  data transfer; otherwise, the value is expressed in bytes.

52.27  –  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
                or the file is not open

52.28  –  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

52.29  –  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

52.30  –  WRITE

  WRITE = wr

  wr   Is a scalar default character variable that is assigned
       one of the following values:

  'YES'     If the file can be written to

  'NO'      If the file cannot be written to

  'UNKNOWN' If the processor cannot determine whether
            the file can be written to

53  –  INTENT

  Specifies the intended use of one or more dummy arguments.

  The INTENT attribute can be specified in a type declaration
  statement or an INTENT statement, and takes one of the following
  forms:

  Type Declaration Statement:

    type, [att-ls,] INTENT (spec) [,att-ls] :: d [, d]...

  Statement:

    INTENT (spec) [::] d [, d]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     spec      Is one of the following specifiers:

               IN    Specifies that the dummy argument must
                     not be redefined (or become undefined)
                     during execution of the procedure.

                     Any associated actual argument must be
                     an expression.

               OUT   Specifies that the dummy argument must be
                     defined before it is referenced in the
                     procedure.

                     Any associated actual argument must be
                     definable.  The argument becomes undefined
                     on entry to the procedure, and is intended
                     only to pass information out of the procedure.

               INOUT Specifies that the dummy argument can both
                     receive data from and return data to the
                     calling program unit.

                     Any associated actual argument must be
                     definable.

     d         Is the name of a dummy argument.  It cannot
               be a dummy procedure or dummy pointer.

  If no INTENT attribute is specified for a dummy argument, its use
  is subject to the limitations of the associated actual argument.

  If a function specifies a defined operator, the dummy arguments
  must have intent IN.

  If a subroutine specifies defined assignment, the first argument
  must have intent OUT or INOUT, and the second argument must have
  intent IN.

  If an actual argument is an array section with a vector subscript,
  it cannot be associated with a dummy array that is defined or
  redefined (has intent OUT or INOUT).

  The INTENT attribute is compatible with the DIMENSION, OPTIONAL,
  TARGET, and VOLATILE attributes.

  EXAMPLES:

  The following example shows type declaration statements specifying
  the INTENT attribute:

    SUBROUTINE TEST(I, J)
      INTEGER, INTENT(IN) :: I
      INTEGER, INTENT(OUT), DIMENSION(I) :: J

  The following are examples of the INTENT statement:

    SUBROUTINE TEST(A, B, X)
       INTENT(INOUT) :: A, B
       ...

    SUBROUTINE CHANGE(FROM, TO)
       USE EMPLOYEE_MODULE
       TYPE(EMPLOYEE) FROM, TO
       INTENT(IN) FROM
       INTENT(OUT) TO
       ...

54  –  INTERFACE

  The first statement of an interface block.  Interface blocks define
  explicit interfaces for external or dummy procedures.  They can
  also be used to define a generic name for procedures, a new
  operator for functions, and a new form of assignment for
  subroutines.  Format:

     INTERFACE [spec]
       [body]...
       [MODULE PROCEDURE nam]...
     END INTERFACE [spec]

     spec  Is one of the following:

           A generic name

           OPERATOR (op)

           The "op" is the defined unary, defined binary,
           or extended intrinsic operator being defined.

           ASSIGNMENT (=)

           A "spec" can only be included in the END INTERFACE
           statement if one was provided in the INTERFACE
           statement; both "spec"s must be identical.

     body  Is one or more function or subroutine subprograms.
           A function must end with END FUNCTION and a subroutine
           must end with END SUBROUTINE.

           The subprogram must not contain a statement function
           or a DATA, ENTRY or FORMAT statement; an entry name
           can be used as a procedure name.

           The subprogram can contain a USE statement.

     nam   Is the name of one or more module procedures that
           are accessible in the host. The MODULE PROCEDURE
           statement is only allowed if the interface block
           specifies a "spec" and has a host that is a module
           (or accesses a module by use association).

           The characteristics of module procedures are not
           given in interface blocks, but are assumed from
           the module subprogram definitions.

  Interface blocks can appear in the specification part of the
  program unit that invokes the external or dummy procedure.

  The characteristics specified for the external or dummy procedure
  must be consistent with those specified in the procedure's
  definition.

  An interface block must not appear in a block data program unit.

  An interface block comprises its own scoping unit, and does not
  inherit anything from its host through host association.

  A procedure must not have more than one explicit interface in a
  given scoping unit.

  For more information, see the HP Fortran for OpenVMS Language
  Reference Manual.

  EXAMPLES:

  The following example shows a simple procedure interface block with
  no generic specification:

    SUBROUTINE SUB_B (B, FB)
      REAL B
      ...
      INTERFACE
        FUNCTION FB (GN)
          REAL FB, GN
        END FUNCTION
      END INTERFACE

54.1  –  Generic Names

  An interface block can be used to specify a generic name to
  reference all of the procedures within the interface block.
  Statement format for initial line in block:

     INTERFACE generic-name

  This kind of interface block can be used to extend or redefine a
  generic intrinsic procedure.

  The procedures that are given the generic name must be the same
  kind of subprogram:  all must be functions, or all must be
  subroutines.

  Any procedure reference involving a generic procedure name must be
  resolvable to one specific procedure; it must be unambiguous.

  EXAMPLES:

    INTERFACE GROUP_SUBS
      SUBROUTINE INTEGER_SUB (A, B)
        INTEGER, INTENT(INOUT) :: A, B
      END SUBROUTINE INTEGER_SUB

      SUBROUTINE REAL_SUB (A, B)
        REAL, INTENT(INOUT) :: A, B
      END SUBROUTINE REAL_SUB

      SUBROUTINE COMPLEX_SUB (A, B)
        COMPLEX, INTENT(INOUT) :: A, B
      END SUBROUTINE COMPLEX_SUB
    END INTERFACE

  The three subroutines can be referenced by their individual
  specific names or by the group name GROUP_SUBS.

  The following example shows a reference to INTEGER_SUB:

  INTEGER V1, V2
  CALL GROUP_SUBS (V1, V2)

54.2  –  Generic Operators

  An interface block can be used to define a generic operator.  The
  only procedures allowed in the interface block are functions that
  can be referenced as defined operations.  Statement format for
  initial line in block:

     INTERFACE OPERATOR (op)

     op  Is one of the following:

         A defined unary  operator (one argument)

         A defined binary  operator (two arguments)

         An extended intrinsic operator (number of arguments
               must be consistent with the intrinsic uses of
               that operator)

  The functions within the interface block must have one or two
  nonoptional arguments with intent IN, and the function result must
  not be of type character with assumed length.  A defined operation
  is treated as a reference to the function.

  EXAMPLES:

    INTERFACE OPERATOR(.BAR.)
      FUNCTION BAR(A_1)
        INTEGER, INTENT(IN) :: A_1
        INTEGER :: BAR
      END FUNCTION BAR
    END INTERFACE

  The following example shows a way to reference function BAR by
  using the new operator:

    INTEGER B
    I = 4 + (.BAR. B)

  The following is an example of a procedure interface block with a
  defined operator extending an existing operator:

    INTERFACE OPERATOR(+)
      FUNCTION LGFUNC (A, B)
      LOGICAL, INTENT(IN) :: A(:), B(SIZE(A))
      LOGICAL :: LGFUNC(SIZE(A))
      END FUNCTION LGFUNC
    END INTERFACE

  The following example shows two equivalent ways to reference
  function LGFUNC:

    LOGICAL, DIMENSION(1:10) :: C, D, E
    N = 10
    E = LGFUNC(C(1:N), D(1:N))
    E = C(1:N) + D(1:N)

54.3  –  Generic Assignment

  An interface block can be used to define generic assignment.  The
  only procedures allowed in the interface block are subroutines that
  can be referenced as defined assignments.  Statement format for
  initial line in block:

     INTERFACE ASSIGNMENT(=)

  The subroutines within the interface block must have two
  nonoptional arguments, the first with intent OUT or INOUT, and the
  second with intent IN.

  A defined assignment is treated as a reference to a subroutine.
  The left side of the assignment corresponds to the first dummy
  argument of the subroutine; the right side of the assignment
  corresponds to the second argument.

  The ASSIGNMENT keyword extends or redefines an assignment operation
  if both sides of the equal sign are of the same derived type.

  Any procedure reference involving generic assignment must be
  resolvable to one specific procedure; it must be unambiguous.

  EXAMPLES:

    INTERFACE ASSIGNMENT (=)
      SUBROUTINE BIT_TO_NUMERIC (NUM, BIT)
      INTEGER, INTENT(OUT) :: NUM
      LOGICAL, INTENT(IN)  :: BIT(:)
      END SUBROUTINE BIT_TO_NUMERIC

      SUBROUTINE CHAR_TO_STRING (STR, CHAR)
      USE STRING_MODULE                    ! Contains definition
                                           !   of type STRING
      TYPE(STRING), INTENT(OUT) :: STR     ! A variable-length string
      CHARACTER(*), INTENT(IN)  :: CHAR
      END SUBROUTINE  CHAR_TO_STRING
    END  INTERFACE

  The following example shows two equivalent ways to reference
  subroutine BIT_TO_NUMERIC:

    CALL BIT_TO_NUMERIC(X, (NUM(I:J)))
    X = NUM(I:J)

  The following example shows two equivalent ways to reference
  subroutine CHAR_TO_STRING:

    CALL CHAR_TO_STRING(CH, '432C')
    CH = '432C'

55  –  INTRINSIC

  Allows the specific name of an intrinsic procedure to be used as an
  actual argument.  (Not all specific names can be used as actual
  arguments.  For more information, see the HP Fortran for OpenVMS
  Language Reference Manual.)

  The INTRINSIC attribute can be specified in a type declaration
  statement or an INTRINSIC statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] INTRINSIC [,att-ls] :: v[,v]...

  Statement:

   INTRINSIC v [,v]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     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
  by means of INTRINSIC statements; these names are recognized as
  intrinsic implicitly.

  The INTRINSIC attribute is compatible with the PRIVATE and PUBLIC
  attributes.

56  –  MAP

  See STATEMENTS STRUCTURE in this Help file.

57  –  MODULE

  A program unit containing specifications and definitions that can
  be made accessible to other program units.  Format:

     MODULE nam
        [specs]
     [CONTAINS
        mod-sub
        [mod-sub]...]
     END [MODULE [nam]]

     nam      Is the name of the module.

     specs    Is one or more specification statements,
              except for the following:

              ENTRY
              FORMAT
              AUTOMATIC (or its equivalent attribute)
              INTENT (or its equivalent attribute)
              OPTIONAL (or its equivalent attribute)
              Statement functions

              An automatic object must not appear in a
              specification statement.

     mod-sub  Is a function or subroutine subprogram that
              defines the the module procedure.  A function
              must end with END FUNCTION and a subroutine
              must end with END SUBROUTINE.

              A module subprogram can contain internal
              procedures.

  If a module name appears following the END statement, it must be
  the same name as the name specified in the MODULE statement.

  The module name cannot be the same as any local name in the main
  program or the name of any other program unit, external procedure,
  or common block in the executable program.

  A module is host to any module procedures it contains, and entities
  in the module are accessible to the module procedures through host
  association.

  A module must not reference itself (either directly or indirectly).

  Although ENTRY statements, FORMAT statements, and statement
  functions are not allowed in the specification part of a module,
  they are allowed in the specification part of a module subprogram.

  Any executable statements in a module can only be specified in a
  module subprogram.

  A module can contain one or more procedure interface blocks, which
  let you specify an explicit interface for an external subprogram or
  dummy subprogram.

  Every internal subprogram must be of the same extrinsic kind as its
  host, and any internal subprogram whose extrinsic kind is not given
  is assumed to be of that extrinsic kind.

  EXAMPLES:

  The following example shows a simple module that can be used to
  provide global data:

    MODULE MOD_A
      INTEGER :: B, C
      REAL E(25,5)
    END MODULE MOD_A
    ...
    SUBROUTINE SUB_Z
      USE MOD_A               ! Makes scalar variables B and C,
                              ! and array E available to this
                              ! subroutine
    END SUBROUTINE SUB_Z

  The following example shows a module procedure:

    MODULE RESULTS
    ...
    CONTAINS
      FUNCTION MOD_RESULTS(X,Y)  ! A module procedure
      ...
      END FUNCTION MOD_RESULTS
    END MODULE RESULTS

  The following example shows a module containing a derived type:

    MODULE EMPLOYEE_DATA
      TYPE EMPLOYEE
        INTEGER ID
        CHARACTER(LEN=40) NAME
      END TYPE EMPLOYEE
    END MODULE

  The following example shows a module containing an interface block:

    MODULE ARRAY_CALCULATOR
      INTERFACE
        FUNCTION CALC_AVERAGE(D)
          REAL :: CALC_AVERAGE
          REAL, INTENT(IN) :: D(:)
        END FUNCTION
      END INTERFACE
    END MODULE ARRAY_CALCULATOR

58  –  MODULE_PROCEDURE

  See STATEMENTS INTERFACE in this Help file.

59  –  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 /group/nlist[[,]/group/nlist]...

     group  Is the name of the group.

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

  Dummy arguments can appear in a namelist.

  The following variables cannot appear in a namelist group:

   o  An array dummy argument with nonconstant bounds

   o  A variable with assumed character length

   o  An allocatable array

   o  An automatic object

   o  A Fortran 95/90 pointer

   o  A variable of a type that has a pointer as an ultimate
      component

   o  A subobject of any of the above objects

  You can use namelist I/O to assign values to elements of arrays or
  substrings of character variables that appear in namelists.

  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 can appear in several namelists.

60  –  NULLIFY

  Disassociates a pointer from its target.  It takes the following
  form:

     NULLIFY (ptr-obj [,ptr-obj]...)

     ptr-obj  Is a structure component or the name of a
              variable; it must be a pointer (have the
              POINTER attribute).

  The initial association status of a pointer is undefined.  You can
  use NULLIFY to initialize an undefined pointer, giving it
  disassociated status.  Then the pointer can be tested using the
  intrinsic function ASSOCIATED.

  EXAMPLES:

     REAL, TARGET  :: TAR(0:50)
     REAL, POINTER :: PTR_A(:), PTR_B(:)
     PTR_A => TAR
     PTR_B => TAR
     ...
     NULLIFY(PTR_A)

  After these statements are executed, PTR_A will have disassociated
  status, while PTR_B will continue to be associated with variable
  TAR.

61  –  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 pathname (or 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 pathname (or 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.

61.1  –  ACCESS

  Indicates the access method for the connection of the file.  It
  takes the following form:

  ACCESS = acc

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

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

61.2  –  ACTION

  Indicates the allowed I/O operations for the file connection.  It
  takes the following form:

  ACTION = act

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

  'READ'      Indicates that only READ statements can refer to
              this connection.
  'WRITE'     Indicates that only WRITE, DELETE, and ENDFILE
              statements can refer to this connection.
  'READWRITE' Indicates that READ, WRITE, DELETE, and ENDFILE
              statements can refer to this connection (*DEFAULT*)

61.3  –  ASSOCIATEVARIABLE

  Indicates a variable that is updated after each direct access I/O
  operation, to reflect the record number of the next sequential
  record in the file.  It takes the following form:

  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.

61.4  –  BLANK

  Indicates how blanks are interpreted in a file.  It takes the
  following form:

  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' (for explicitly OPENed files, preconnected
  files, and internal files).

  If the BN or BZ edit descriptors are specified for a formatted
  input statement, they supersede the default interpretation of
  blanks.

61.5  –  BLOCKSIZE

  Indicates the physical I/O transfer size for the file.  It takes
  the following form:

  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; it is determined
  by RMS defaults.

  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.  The default is the
  smallest value capable of holding a single record.

61.6  –  BUFFERCOUNT

  Indicates the number of buffers to be associated with the logical
  unit for multibuffered I/O.  It takes the following form:

  BUFFERCOUNT = bc

  bc  Is a numeric expression.

  The range of values for "bc" is 1 to 127.

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

61.7  –  BUFFERED

  Indicates run-time library behavior following WRITE operations.  It
  takes the following form:

  BUFFERED = bf

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

       'NO'   Requests that the run-time library send output
              data to the file system after each WRITE
              operation.

       'YES'  Requests that the run-time library accumulate
              output data in its internal buffer, possibly
              across several WRITE operations, before the data
              is sent to the file system.

              Buffering may improve run-time performance
              for output-intensive applications.

  The default is 'NO'.

  On OpenVMS, BUFFERED has no effect.  The operating system
  automatically performs buffering, which can be affected by the
  values of the BUFFERCOUNT and BUFFERSIZE keywords when the file is
  opened.

61.8  –  CARRIAGECONTROL

  Indicates the type of carriage control used when a file is
  displayed at a terminal.  It takes the following form:

  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'.

61.9  –  CONVERT

  Indicates a nonnative numeric format for unformatted data.  It
  takes the following form:

  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,
                      INTEGER*4, or INTEGER*8) and IEEE
                      floating-point data of the appropriate size
                      and type (REAL*4, REAL*8, REAL*16, COMPLEX*8,
                      COMPLEX*16, or COMPLEX*32).  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, INTEGER*4, or
                      INTEGER*8) and IEEE floating-point data of
                      the appropriate size and type (REAL*4, REAL*8,
                      REAL*16, COMPLEX*8, COMPLEX*16, or COMPLEX*32).
                      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, INTEGER*4, or
                      INTEGER*8) and CRAY floating-point data of
                      size REAL*8 or COMPLEX*16.

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

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

     'IBM' -          Big endian integer data of the appropriate
                      size (INTEGER*1, INTEGER*2, INTEGER*4, or
                      INTEGER*8) 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, INTEGER*4, or
                      INTEGER*8) and HP VAX floating-point
                      data of format F_floating for size
                      REAL*4 or COMPLEX*8, D_floating for size
                      REAL*8 or COMPLEX*16, and H_floating for
                      REAL*16 or COMPLEX*32.

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

     '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 an OpenVMS logical name or the compiler
  option /CONVERT (or OPTIONS/CONVERT).  The order of precedence is
  OpenVMS 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)

61.10  –  DEFAULTFILE

  Indicates a default file specification string.  It takes the
  following form:

  DEFAULTFILE = ce

  ce  Is a character expression.

  This specifier 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')

61.11  –  DELIM

  Indicates what characters (if any) are used to delimit character
  constants in list-directed and namelist output.  It takes the
  following form:

  DELIM = del

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

  'APOSTROPHE'  Indicates that apostrophes delimit character
                constants. All internal apostrophes are doubled.

  'QUOTE'       Indicates that quotation marks delimit character
                constants.  All internal quotation marks are doubled.

  'NONE'        Indicates that character constants have no
                delimiters.  No internal apostrophes or quotation
                marks are doubled. This is the default.

  DELIM is only allowed for files connected for formatted data
  transfer; it is ignored during input.

61.12  –  DISPOSE

  Indicates the status of the file after the unit is closed.  It
  takes one of the following forms:

  DISP = dis
  DISPOSE = 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.

61.13  –  ERR

  Identifies a branch target statement that receives control if an
  error occurs.  It takes the following form:

  ERR = s

  s  Is the label of an executable statement

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

61.14  –  EXTENDSIZE

  Indicates the number of blocks by which to extend a disk file
  (extent) when additional storage space is needed.  It takes the
  following form:

  EXTENDSIZE = e

     e  Is a numeric expression.

  The space used to extend a file is contiguous if possible.
  Otherwise, noncontiguous space is used.  The default is the system
  default for the device.

61.15  –  FILE

  Indicates the name of the file to be connected to the unit.  It
  takes the following form:

  FILE = name

  name   Is a character or numeric expression.

  The "name" can be any pathname (or specification) allowed by the
  operating system.  (See the appropriate manual in the OpenVMS
  operating system documentation set.)

  Any trailing blanks in the name are ignored.

  If the following conditions occur:

   o  FILE is omitted

   o  The unit is not connected to a file

   o  STATUS='SCRATCH' is not specified

  then VSI Fortran generates a file name in the form FORnnn.DAT,
  where "nnn" is the logical unit number (with leading zeros, if
  necessary).

  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.

61.16  –  FORM

  Indicates whether the file is being connected for formatted,
  unformatted, or binary data transfer.  It takes the following form:

  FORM = ft

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

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

61.17  –  INITIALSIZE

  Indicates the number of blocks in the initial storage allocation
  (extent) for a disk file.  It takes the following form:

  INITIALSIZE = e

     e  Is a numeric expression.

  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.

61.18  –  IOSTAT

  Designates a variable to store a value indicating the status of a
  data transfer operation.  It takes the following form:

  IOSTAT = ios

  ios   Is a scalar default integer variable.

  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 subsequent I/O operations on the logical unit that is
  opened.  However, you can use the IOSTAT parameter in subsequent
  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 VMS condition handler.  (For
  more information, see the HP Fortran for OpenVMS User Manual.)

61.19  –  KEY

  Defines the access keys for records in an indexed file.  It takes
  the following form:

  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 is the
  primary key (the default key).  It usually has a unique value for
  each record.

  You can also define alternate keys.  RMS allows up to 254 alternate
  keys.

  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
  subsequent I/O operations.

  However, if you use the KEY parameter for an existing file, your
  specification must be identical to the established key attributes.

  Subsequent 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.

61.20  –  MAXREC

  Indicates the maximum number of records that can be transferred
  from or to a direct access file while the file is connected.  It
  takes the following form:

  MAXREC = mr

  mr  Is an numeric expression.

  The default is the maximum allowed (2**32-1).

61.21  –  NAME

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

61.22  –  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.

61.23  –  ORGANIZATION

  Indicates the internal organization of the file.  It takes the
  following form:

  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.

61.24  –  PAD

  Indicates whether a formatted input record is padded with blanks
  when an input list and format specification requires more data than
  the record contains.  It takes the following form:

  PAD = pd

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

  'YES'  Indicates the record will be padded with blanks
         when necessary (the default).

  'NO'   Indicates the record will not be padded with blanks.
         The input record must contain the data required by
         the input list and format specification.

  This behavior is different from FORTRAN 77, which never pads short
  records with blanks.  For example, consider the following:

    READ (5,'(I5)') J

  If you enter 123 followed by a carriage return, FORTRAN 77 will
  turn the I5 into an I3 and J will be assigned 123.

  However, VSI Fortran pads the 123 with 2 blanks unless you
  explicitly open the unit with PAD='NO'.

  You can override blank padding by explicitly specifying the BN edit
  descriptor.

  The PAD specifier is ignored during output.

61.25  –  POSITION

  Indicates the position of a file connected for sequential access.
  It takes the following form:

  POSITION = pos

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

  'ASIS'   Indicates the file position is unchanged if the file
           exists and is already connected.  The position is
           unspecified if the file exists but is not connected.
           This is the default.

  'REWIND' Indicates the file is positioned at its initial point.

  'APPEND' Indicates the file is positioned at its terminal point
           (or before its end-of-file record, if any).)

  A new file (whether specified as new explicitly or by default) is
  always positioned at its initial point.

61.26  –  READONLY

  READONLY

  Prohibits WRITE access to the file.  Enables users with READ access
  to access the file.

  READONLY is similar to specifying ACTION='READ', but READONLY
  prevents deletion of the file if it is closed with STATUS='DELETE'
  in effect.

  Default file access privileges are READWRITE, which can cause
  run-time I/O errors if the file protection does not permit write
  access.

  The READONLY specifier 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, use READONLY
  if you wish to open a file so you can read it, but you also want
  others to be able to read the same file while you have it open.

61.27  –  RECL

  Indicates the length of logical records in a file connected for
  direct or keyed access, or the maximum length of a record in a file
  connected for sequential access.  It takes the following form:

  RECL = rl

  rl  Is an numeric expression.  If necessary, the value is
      converted to integer data type before use.

  If the file is connected for formatted data transfer, the value
  must be expressed in bytes (characters).  Otherwise, the value is
  expressed in 4-byte units (longwords).  If the file is connected
  for unformatted data transfer, the value can be expressed in bytes
  if compiler option /ASSUME=BYTERECL is specified.

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

  The length specified is interpreted depending on the type of
  records in the connected file, as follows:

   o  For segmented records, RECL indicates the maximum length for
      any segment (not including the two segment control bytes).

   o  For fixed-length records, RECL indicates the size of each
      record.

   o  For variable-length or stream records, RECL specifies the size
      of the buffer that will be allocated to hold records read or
      written.  Specifying RECL for stream records (STREAM, STREAMCR
      or STREAMLF) is required if the longest record length in the
      file exceeds the default RECL value.

  Errors occur under the following conditions:

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

   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

  The following table lists the maximum values that can be specified
  for "rl" 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
  may be less, as described in the OpenVMS Record Management
  Services Reference Manual.

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

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

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

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

  The default value depends on the setting of the RECORDTYPE
  specifier, as follows:

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

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

61.28  –  RECORDSIZE

  RECORDSIZE is the nonstandard synonym for RECL (see OPEN RECL).

61.29  –  RECORDTYPE

  Indicates the type of records in a file.  It takes the following
  form:

  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 may 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 is a logical record consisting of one or more
  variable-length records (segments).  The logical record can span
  several physical records.  Only unformatted sequential-access files
  with sequential organization can have segmented records;
  'SEGMENTED' must not be specified for any other file type.

  Files containing segmented records can be accessed only by
  unformatted sequential data transfer statements.  You cannot use an
  unformatted READ statement to access such a file, unless you
  specify RECORDTYPE='SEGMENTED' in the OPEN statement.

  Normally, if you do not use the RECORDTYPE specifier when you are
  accessing an existing file, the record type of the file is used.
  However, if the file is an unformatted sequential-access file with
  sequential organization and variable-length records, the default
  record type is 'SEGMENTED'.

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

  If an output statement does not specify a full record for a file
  containing fixed-length records, the following occurs:

   o  In formatted files, the record is filled with blanks

   o  In unformatted files, the record is filled with zeros

61.30  –  SHARED

  SHARED

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

  For more information on file sharing, see the HP Fortran for
  OpenVMS User Manual.

61.31  –  STATUS

  Indicates the status of a file when it is opened.  It takes the
  following form:

  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.

  'REPLACE'   Replace the file with another. If the file to be
              replaced exists, it is deleted and a new file is
              created with the same name.  If the file to be replaced
              does not exist, a new file is created and its status
              changes to 'OLD'.

  '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 compiler option /NOF77 (or OPTIONS
  /NOF77), the default value is 'NEW'.  If you implicitly open a file
  using READ, the default 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 indicate a different device, use
  the FILE specifier.

                                 NOTE

          The  STATUS  parameter  is  also  used   in   CLOSE
          statements  to  specify  the status of a file after
          the file is closed.  However, in  CLOSE  statements
          the  STATUS values are the same as those listed for
          the DISPOSE specifier (see OPEN DISPOSE).

61.32  –  TYPE

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

61.33  –  UNIT

  Indicates the logical unit to which a file is to be connected.  It
  takes the following form:

  [UNIT=] u

  u  Is a numeric expression

  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.

61.34  –  USEROPEN

  Indicates a user-written external function that controls the
  opening of the file.  It takes the following form:

  USEROPEN = func

  func  Is the symbolic name of the USEROPEN function.

  The function must be declared in a previous EXTERNAL statement; if
  it is typed, it must be INTEGER*4.

62  –  OPTIONAL

  Permits dummy arguments to be omitted in a procedure reference.

  The OPTIONAL attribute can be specified in a type declaration
  statement or an OPTIONAL statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] OPTIONAL [,att-ls] :: d-arg [,d-arg]...

  Statement:

   OPTIONAL [::] d-arg [,d-arg]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     d-arg     Is the name of a dummy argument.

  The OPTIONAL attribute can only appear in the scoping unit of a
  subprogram or an interface body, and can only be specified for
  dummy arguments.

  A dummy argument is "present" if it associated with an actual
  argument.  A dummy argument that is not optional must be present.
  You can use the PRESENT intrinsic function to determine whether an
  optional dummy argument is associated with an actual argument.

  To call a procedure that has an optional argument, you must use an
  explicit interface.

  The OPTIONAL attribute is compatible with the DIMENSION, EXTERNAL,
  INTENT, POINTER, TARGET, and VOLATILE attributes.

  EXAMPLES:

  The following example shows a type declaration statement specifying
  the OPTIONAL attribute:

    SUBROUTINE TEST(A)
    REAL, OPTIONAL, DIMENSION(-10:2) :: A
    END SUBROUTINE

  The following is an example of the OPTIONAL statement:

         SUBROUTINE TEST(A, B, L, X)
         OPTIONAL :: B
         INTEGER A, B, L, X

         IF (PRESENT(B)) THEN        ! Printing of B is conditional
            PRINT *, A, B, L, X      !   on its presence
         ELSE
            PRINT *, A, L, X
         ENDIF
         END SUBROUTINE

         INTERFACE
            SUBROUTINE TEST(ONE, TWO, THREE, FOUR)
             INTEGER ONE, TWO, THREE, FOUR
             OPTIONAL :: TWO
           END SUBROUTINE
         END INTERFACE

         INTEGER I, J, K, L

         I = 1
         J = 2
         K = 3
         L = 4

         CALL TEST(I, J, K, L)            ! Prints:  1  2  3  4
         CALL TEST(I, THREE=K, FOUR=L)    ! Prints:  1  3  4
         END

  Note that in the second call to subroutine TEST, the second
  positional (optional) argument is omitted.  In this case, all
  following arguments must be keyword arguments.

63  –  OPTIONS

  Overrides or confirms the compiler options in effect for a program
  unit.  Statement format:

     OPTIONS option [option...]

     option  Is one of the following:

     /ASSUME=[NO]UNDERSCORE

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

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

     /[NO]EXTEND_SOURCE
     /[NO]F77
     /FLOAT=(D_FLOAT, G_FLOAT, IEEE_FLOAT)
     /[NO]G_FLOATING
     /[NO]I4
     /[NO]RECURSIVE

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

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

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

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

64  –  PARAMETER

  Associates a symbolic name with a constant value.

  The PARAMETER attribute can be specified in a type declaration
  statement or an PARAMETER statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] PARAMETER [,att-ls] :: p=c [,p=c]...

  Statement:

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

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     p  Is the symbolic name of the constant.

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

  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.

  The PARAMETER attribute is compatible with the PRIVATE and PUBLIC
  attributes.

  For information on an alternate syntax for PARAMETER, see Help
  topic:  COMPATIBILITY_FEATURES PARAMETER.

65  –  PAUSE

  The PAUSE statement displays a message on the terminal and
  temporarily suspends program execution, so that you can take some
  action.  This statement has been deleted in Fortran 95; it was an
  obsolescent feature in Fortran 90.  VSI Fortran fully supports
  features deleted in Fortran 95.

  Statement format:

     PAUSE [disp]

     disp  Is an optional character constant or a string of
           up to six digits.  (Fortran 95/90 and FORTRAN 77 limit
           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 VMS 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.

66  –  POINTER

  Specifies that an object is a pointer.

  The POINTER attribute can be specified in a type declaration
  statement or an POINTER statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] POINTER [,att-ls] :: ptr [(spec)] [,ptr [(spec)]]...

  Statement:

   POINTER [::] ptr [(spec)] [,ptr [(spec)]]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     ptr       Is the name of the pointer.  The pointer
               cannot be declared with the INTENT or
               PARAMETER attributes.

     spec      Is a deferred-shape specification
               (: [,:]...).

  A pointer must not be referenced or defined unless it becomes
  pointer associated (through pointer assignment or an ALLOCATE
  statement) with a target object that can be referenced or defined.
  An object with the POINTER attribute has no initial storage set
  aside for it.

  If the pointer is an array, and it is given the DIMENSION attribute
  elsewhere in the program, it must be declared as a deferred-shape
  array.

  A pointer cannot be specified in an EQUIVALENCE or NAMELIST
  statement.

  The POINTER attribute is compatible with the AUTOMATIC, DIMENSION
  (with deferred shape), OPTIONAL, PRIVATE, PUBLIC, SAVE, STATIC, and
  VOLATILE attributes.

  EXAMPLES:

  The following example shows type declaration statements specifying
  the POINTER attribute:

     TYPE(SYSTEM), POINTER :: CURRENT, LAST
     REAL, DIMENSION(:,:), POINTER :: I, J, REVERSE

  The following is an example of the POINTER statement:

     TYPE(SYSTEM) :: TODAYS
     POINTER :: TODAYS, A(:,:)

67  –  PRINT

  Transfers output data from internal storage to external records
  that are sequentially accessed.

67.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.

67.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.

67.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=.

68  –  PRIVATE and PUBLIC

  Specify the accessibility of entities in a module.  (These
  attributes are also called accessibility attributes.)

  The PRIVATE and PUBLIC attributes can be specified in a type
  declaration statement or in a PRIVATE or PUBLIC statement, and take
  one of the following forms:

  Type Declaration Statement:

   type, [att-ls,] PRIVATE [,att-ls] :: ent [,ent]...
   type, [att-ls,] PUBLIC  [,att-ls] :: ent [,ent]...

  Statement:

   PRIVATE [[::] ent [,ent]...]
   PUBLIC  [[::] ent [,ent]...]

    type      Is a data type specifier.

    att-ls    Is an optional list of attribute specifiers.

    ent       Is one of the following:

              A variable name
              A procedure name
              A derived type name
              A named constant
              A namelist group name

              In statement form, an entity can also be
              a generic identifier (a generic name,
              defined operator, or defined assignment).

  The PRIVATE and PUBLIC attributes can only appear in the scoping
  unit of a module.

  Only one PRIVATE or PUBLIC statement without an entity list is
  permitted in the scoping unit of a module; it sets the default
  accessibility of all entities in the module.

  If no PUBLIC or PRIVATE statements are specified in a module, the
  default is PUBLIC accessibility.  Entities with PUBLIC
  accessibility can be accessed from outside the module by means of a
  USE statement.

  If a derived type is declared PRIVATE in a module, its components
  are also PRIVATE.  The derived type and its components are
  accessible to any subprograms within the defining module through
  host association, but they are not accessible from outside the
  module.

  If the derived type is declared PUBLIC in a module, but its
  components are declared PRIVATE, any scoping unit accessing the
  module though use association (or host association) can access the
  derived-type definition, but not its components.

  If a module procedure has a dummy argument or a function result of
  a type that has PRIVATE accessibility, the module procedure must
  have PRIVATE accessibility.  If the module has a generic
  identifier, it must also be declared PRIVATE.

  If a procedure has a generic identifier, the accessibility of the
  procedure's specific name is independent of the accessibility of
  its generic identifier.  One can be declared PRIVATE and the other
  PUBLIC.

  The PRIVATE attribute is compatible with the ALLOCATABLE,
  DIMENSION, EXTERNAL, INTRINSIC, PARAMETER, POINTER, SAVE, STATIC,
  TARGET, and VOLATILE attributes.

  The PUBLIC attribute is compatible with the ALLOCATABLE, DIMENSION,
  EXTERNAL, INTRINSIC, PARAMETER, POINTER, SAVE, STATIC, TARGET, and
  VOLATILE attributes.

  EXAMPLES:

  The following examples show type declaration statements specifying
  the PUBLIC and PRIVATE attributes:

     REAL,  PRIVATE  :: A, B, C
     INTEGER, PUBLIC :: LOCAL_SUMS

  The following is an example of the PUBLIC and PRIVATE statements:

     MODULE SOME_DATA
       REAL ALL_B
       PUBLIC ALL_B
       TYPE RESTRICTED_DATA
         REAL LOCAL_C
         DIMENSION LOCAL_C(50)
       END TYPE RESTRICTED_DATA
       PRIVATE RESTRICTED_DATA
     END MODULE

  The following derived-type declaration statement indicates that the
  type is restricted to the module:

     TYPE, PRIVATE  :: DATA
       ...
     END TYPE DATA

  The following example shows a PUBLIC type with PRIVATE components:

     MODULE MATTER
       TYPE ELEMENTS
         PRIVATE
         INTEGER C, D
       END TYPE
     ...
     END MODULE MATTER

  In this case, components C and D are private to type ELEMENTS, but
  type ELEMENTS is not private to MODULE MATTER.  Any program unit
  that uses the module MATTER, can declare variables of type
  ELEMENTS, and pass as arguments values of type ELEMENTS.

69  –  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.

  The main program cannot contain the following attributes:  INTENT,
  OPTIONAL, PRIVATE, or PUBLIC.

  A main program can contain an internal subprogram (defines an
  internal procedure).  It must be preceded by a CONTAINS statement.

70  –  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=.

     eor      Is the label of a statement to which control is
              transferred in the event of an end-of-record.
              Optionally prefaced by EOR=.  This can only
              be specified for nonadvancing READs.

     adv      Specifies advancing (ADVANCE='YES') or nonadvancing
              input (ADVANCE='NO').  The default is 'YES'.

     size     Specifies character count (SIZE=int). It can
              only be indicated for nonadvancing READs.

     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=.

     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.

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

70.1  –  Sequential

70.1.1  –  Formatted

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

  1. READ (extu, fmt [,adv][,size][,iostat][,err][,end][,eor]) [iolist]

     Reads from a specified external unit.

  2. READ fmt [,iolist]

     Reads from FOR$READ (normally, the terminal).

70.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.

70.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 nml

     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.

70.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.

70.2  –  Direct

70.2.1  –  Formatted

  Formatted direct READ statement format:

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

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

70.2.2  –  Unformatted

  Unformatted direct READ statement format:

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

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

70.3  –  Indexed

70.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".

70.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.

70.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".

71  –  RECORD

  Creates a record structure 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 of 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, EQUIVALENCE, or NAMELIST statements.

  Records initially have undefined values unless you have defined
  their values in structure declarations.

  See also COMPATIBILITY_FEATURES RECORD_STRUCTURE in this Help file.

72  –  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.

                                 NOTE

          An alternate return is an  obsolescent  feature  in
          Fortran  95  and  Fortran 90.  VSI Fortran fully
          supports this feature.

  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.

73  –  REWIND

  Positions a sequential or direct access file at the beginning of
  the file.  Do not use a REWIND statement for a file that is open
  for indexed access.  Use this statement 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=.

  The unit number must refer to a file on disk or magnetic tape, and
  the file must be open for sequential, direct, or append access.

  If a REWIND is done on a direct access file, the NEXTREC specifier
  is assigned a value of 1.

  A REWIND statement must not be specified for a file that is open
  for keyed access.

  If a file is already positioned at the initial point, a REWIND
  statement has no effect.

  If a REWIND statement is specified for a unit that is not open, it
  has no effect.

  See also STATEMENTS BACKSPACE in this Help file.

74  –  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

75  –  SAVE

  Causes the values and definition of objects to be saved across
  invocations of a subprogram.

  The SAVE attribute can be specified in a type declaration statement
  or SAVE statement, and takes one of the following forms:

  Type Declaration Statement:

   type, [att-ls,] SAVE [,att-ls] :: [obj [,obj]...]

  Statement:

   SAVE [obj [,obj]...]

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     obj       Is the name of an object, or the name of a
               common block enclosed in slashes (such as
               /CBLOCK/).

  In VSI Fortran, the definitions of COMMON variables, and local
  variables of non-recursive subprograms (other than allocatable
  arrays or variables declared AUTOMATIC), are saved by default.  To
  enhance portability and avoid possible compiler warning messages,
  HP recommends that you use the SAVE statement to name variables
  whose values you want to preserve between subprogram invocations.

  When a SAVE statement does not explicitly contain a list, all
  allowable items in the scoping unit are saved.

  A SAVE statement cannot specify the following (their values cannot
  be saved):

   o  A blank common

   o  An object in a common block

   o  A procedure

   o  A dummy argument

   o  A function result

   o  An automatic object

   o  A PARAMETER (named) constant

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

  If a common block is saved in any scoping unit of a program (other
  than the main program), it must be saved in every scoping unit in
  which the common block appears.

  A SAVE statement has no effect in a main program.

  The SAVE attribute is compatible with the ALLOCATABLE, DIMENSION,
  POINTER, PRIVATE, PUBLIC, STATIC, TARGET, and VOLATILE attributes.

76  –  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.

  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.

                                 NOTE

          This  statement  is  obsolescent  in  Fortran   95.
          HP  Fortran  flags  obsolescent  features,  but
          fully supports them.

77  –  SELECT_CASE

  See STATEMENTS CASE in this Help file.

78  –  SEQUENCE

  Permitted for derived types.  Allows derived-type components to be
  used in COMMON and EQUIVALENCE statements.

  See DATA DERIVED_TYPES TYPE_DEFINITIONS in this Help file.

79  –  STOP

  Terminates program execution.  Statement format:

     STOP [disp]

     disp  Is a character constant or a string of up to
           six digits.  (Fortran 95/90 and FORTRAN 77 limit
           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", no message is displayed.

80  –  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
             subsequent 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.

  Subsequent 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 declaration 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.

  By default, fields are aligned on natural boundaries; misaligned
  fields are padded as necessary.  To avoid padding of records, you
  should lay out structures so that all fields are naturally aligned.

  To pack fields on arbitrary byte boundaries, you must specify a
  compiler option.  You can also specify alignment for fields by
  using the cDEC$ OPTIONS general directive.

  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

  See also COMPATIBILITY_FEATURES RECORD_STRUCTURE in this Help file.

80.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.

80.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.

80.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 of 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 utilized 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

80.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 subsequent PARAMETER statement declares a
  new, different symbol which 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.

81  –  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:

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

     prefx Is one of the following keywords:

           RECURSIVE    Permits direct recursion to occur.

           PURE         Restricts the procedure from having
                        side effects.

           ELEMENTAL    Specifies PURE with certain constraints
                        on a dummy argument:

                        o It must be scalar and cannot have the
                          POINTER attribute.
                        o It cannot appear in a specification
                          expression, except as an argument to the
                          BIT_SIZE, KIND, or LEN intrinsic functions
                          or the numeric inquiry intrinsic functions
                        o It must not be *
                        o It must not be a dummy procedure

                        An explicit interface must be visible to the
                        caller of an ELEMENTAL procedure.

                        If ELEMENTAL is specified, RECURSIVE must not
                        be specified.

     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.

82  –  TARGET

  Specifies that an object can become the target of a pointer.

  The TARGET attribute can be specified in a type declaration
  statement or TARGET statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] TARGET [,att-ls] :: obj [spec] [,obj [spec]]...

  Statement:

   TARGET [::] obj [spec] [,obj [spec]]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     obj       Is the name of an object.  The object must
               not be declared with the PARAMETER attribute.

     spec      Is an array specification.

  A pointer is associated with a target by pointer assignment or by
  an ALLOCATE statement.

  If an object does not have the TARGET attribute or has not been
  allocated (using an ALLOCATE statement), no part of it can be
  accessed by a pointer.

  The TARGET attribute is compatible with the ALLOCATABLE, AUTOMATIC,
  DIMENSION, INTENT, OPTIONAL, PRIVATE, PUBLIC, SAVE, STATIC, and
  VOLATILE attributes.

  EXAMPLES:

  The following example shows type declaration statements specifying
  the TARGET attribute:

     TYPE(SYSTEM), TARGET :: FIRST
     REAL, DIMENSION(20, 20), TARGET :: C, D

  The following is an example of a TARGET statement:

     TARGET :: C(50, 50), D

83  –  TYPE

  Transfers output data from internal storage to external records
  that are sequentially accessed.

83.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.

83.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.

83.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=.

84  –  Type declaration

  Explicitly specifies the properties of data objects or functions.

  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.

84.1  –  Numeric

  Statement format:

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

     type   Is any of the following data type specifiers:

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

     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 HP Fortran for OpenVMS
            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.

     att    Is one of the following attribute specifiers:

            ALLOCATABLE       POINTER
            AUTOMATIC         PRIVATE
            DIMENSION         PUBLIC
            EXTERNAL          SAVE
            INTENT            STATIC
            INTRINSIC         TARGET
            OPTIONAL          VOLATILE
            PARAMETER

     v      Is the name of a data object or function.  It can
            optionally be followed by:

            o An array specification, if the object is an array
            o A character length, if the object is of type
              character
            o An initialization expression or, for pointer
              objects, =>NULL()

     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 specifications 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 item unless it initializes an array.  When the "clist"
  initializes an array, it must contain a value for every element in
  the array.

  If =>NULL() appears for a pointer, the pointer's initial
  association status is disassociated.

  In a function declaration, an array must be a deferred-shape array
  if it has the POINTER attribute; otherwise, it must be an
  explicit-shape array.

  The double colon separator (::) is required only if the declaration
  contains an attribute specifier or an initialization expression;
  otherwise it is optional.

  The same attribute must not appear more than once in a given type
  declaration statement, and an entity cannot be given the same
  attribute more than once in a scoping unit.

  If the PARAMETER attribute is specified, the declaration must
  contain an initialization expression.

  The following objects cannot be initialized in a type declaration
  statement:

   o  A dummy argument

   o  A function result

   o  An object in a named common block (unless the type declaration
      is in a block data program unit)

   o  An object in blank common

   o  An allocatable array

   o  A pointer

   o  An external name

   o  An intrinsic name

   o  An automatic object

   o  An object that has the AUTOMATIC attribute

84.2  –  Character

  Format:

     CHARACTER[*len[,] [[,att]...::] 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.

     att    Is one of the following attribute specifiers:

            ALLOCATABLE       POINTER
            AUTOMATIC         PRIVATE
            DIMENSION         PUBLIC
            EXTERNAL          SAVE
            INTENT            STATIC
            INTRINSIC         TARGET
            OPTIONAL          VOLATILE
            PARAMETER

     v      Is the symbolic name of a constant, variable, array,
            statement function or function subprogram, or array
            specification. 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 65535.  If no length
  is specified, a length of 1 is assumed.

  Character type declaration statements can define arrays if they
  include array specifications in their list.  The array
  specification goes first if both an array specification 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.

  In a function declaration, an array must be a deferred-shape array
  if it has the POINTER attribute; otherwise, it must be an
  explicit-shape array.

  The double colon separator (::) is required only if the declaration
  contains an attribute specifier or an initialization expression;
  otherwise it is optional.

  The same attribute must not appear more than once in a given type
  declaration statement, and an entity cannot be given the same
  attribute more than once in a scoping unit.

  If the PARAMETER attribute is specified, the declaration must
  contain an initialization expression.

  The following objects cannot be initialized in a type declaration
  statement:

   o  A dummy argument

   o  A function result

   o  An object in a named common block (unless the type declaration
      is in a block data program unit)

   o  An object in blank common

   o  An allocatable array

   o  A pointer

   o  An external name

   o  An intrinsic name

   o  An automatic object

   o  An object that has the AUTOMATIC attribute

                                 NOTE

          The CHARACTER*len form for a CHARACTER  declaration
          is obsolescent in Fortran 95.  VSI Fortran flags
          obsolescent features, but fully supports them.

85  –  UNION

  See STATEMENTS STRUCTURE (subheads TYPE_DECLARATIONS and
  UNION_DECLARATIONS) in this Help file.

86  –  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  A scalar default integer variable that is
          defined as a positive integer if an error occurs
          and zero if no error occurs.

87  –  USE

  Gives a program unit accessibility to public entities in a module.
  It takes one of the following forms:

     USE name [, rename-ls]
     USE name, ONLY : [only-ls]

     name       Is the name of the module.

     rename-ls  Is one or more items having the following
                form:

        local-name => mod-name

        local-name  Is the name of the entity in the program
                    unit using the module.

        mod-name    Is the name of a public entity in the module.

     only-ls   Is the name of a public entity in the module
               or a generic identifier (a generic name, defined
               operator, or defined assignment).

               An entity in the "only-ls" can also take the form:

        [local-name =>] mod-name

  If the USE statement is specified without the ONLY option, the
  program unit has access to all public entities in the named module.

  If the USE statement is specified with the ONLY option, the program
  unit has access to only those entities following the option.

  If more than one USE statement for a given module appears in a
  scoping unit, the following rules apply:

   o  If one USE statement does not have the ONLY option, all public
      entities in the module are accessible, and any "rename-ls"s and
      "only-ls"s are interpreted as a single, concatenated
      "rename-ls".

   o  If all the USE statements have ONLY options, all the "only-ls"s
      are interpreted as a single, concatenated "only-ls".  Only
      those entities named in one or more of the "only-ls"s are
      accessible.

  If two or more generic interfaces that are accessible in a scoping
  unit have the same name, the same operator, or are both
  assignments, they are interpreted as a single generic interface.
  Otherwise, multiple accessible entities can have the same name only
  if no reference to the name is made in the scoping unit.

  The local names of entities made accessible by a USE statement must
  not be respecified with any attribute other than PUBLIC or PRIVATE.
  The local names can appear in namelist group lists, but not in a
  COMMON or EQUIVALENCE statement.

  EXAMPLES:

  The following shows examples of the USE statement:

    MODULE MOD_A
      INTEGER :: B, C
      REAL E(25,5), D(100)
    END MODULE MOD_A
    ...
    SUBROUTINE SUB_Y
      USE MOD_A, DX => D, EX => E   ! Array D has been renamed
                                    ! DX and array E
      ...                           ! has been renamed EX. Scalar
                                    ! variables B
    END SUBROUTINE SUB_Y            ! and C are also available to
    ...                             ! this subroutine (using their
                                    ! module names).
    SUBROUTINE SUB_Z
      USE MOD_A, ONLY: B, C         ! Only scalar variables B and
                                    ! C are
      ...                           ! available to this subroutine
    END SUBROUTINE SUB_Z
    ...

  The following example shows a module containing common blocks:

    MODULE COLORS
      COMMON /BLOCKA/ C, D(15)
      COMMON /BLOCKB/ E, F
      ...
    END MODULE COLORS
    ...
    FUNCTION HUE(A, B)
      USE COLORS
      ...
    END FUNCTION HUE

  The USE statement makes all of the variables in the common blocks
  in module COLORS available to the function HUE.

  To provide data abstraction, a user-defined data type and
  operations to be performed on values of this type can be packaged
  together in a module.  The following example shows such a module:

    MODULE CALCULATION
      TYPE ITEM
        REAL :: X, Y
      END TYPE ITEM

      INTERFACE OPERATOR (+)
        MODULE PROCEDURE ITEM_CALC
      END INTERFACE

    CONTAINS
      FUNCTION ITEM_CALC (A1, A2)
        TYPE(ITEM) A1, A2, ITEM_CALC
        ...
      END FUNCTION ITEM_CALC
      ...
    END MODULE CALCULATION

    PROGRAM TOTALS
    USE CALCULATION
    TYPE(ITEM) X, Y, Z
      ...
      X = Y + Z
      ...
    END

  The USE statement allows program TOTALS access to both the type
  ITEM and the extended intrinsic operator + to perform calculations.

88  –  VIRTUAL

  See COMPATIBILITY_FEATURES in this Help file.

89  –  VOLATILE

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

  The VOLATILE attribute can be specified in a type declaration
  statement or VOLATILE statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] VOLATILE [,attr-ls] :: obj [,obj]...

  Statement:

   VOLATILE obj [,obj]...

     type      Is a data type specifier.

     attr-ls   Is an optional list of attribute specifiers.

     obj       Is the name of an object or a common block
               enclosed in slashes.

  A variable or COMMON block must be declared VOLATILE if it can be
  read or written in a way that is not visible to the compiler.  For
  example:

   o  If an operating system feature is used to place a variable in
      shared memory (so that it can be accessed by other programs),
      the variable must be declared VOLATILE.

   o  If a variable is modified by a routine called by the operating
      system when an asynchronous event occurs, the variable must be
      declared VOLATILE.

  If an array is declared VOLATILE, each element in the array becomes
  volatile.  If a common block is declared VOLATILE, each variable in
  the common block becomes volatile.

  If an object of derived type is declared VOLATILE, its components
  become volatile.

  If a pointer is declared VOLATILE, the pointer itself becomes
  volatile.

  A VOLATILE statement cannot specify the following:

   o  A procedure

   o  A function result

   o  A namelist group

  The VOLATILE attribute is compatible with the ALLOCATABLE,
  AUTOMATIC, DIMENSION, INTENT, OPTIONAL, POINTER, PRIVATE, PUBLIC,
  SAVE, STATIC, and TARGET attributes.

90  –  WHERE

  Permits masked array assignment, which lets you perform an array
  operation on selected elements.  This kind of assignment masks the
  evaluation of expressions and assignment of values in array
  assignment statements, according to the value of a logical array
  expression.

  WHERE can be specified as a construct or statement.  Format:

  Statement form:

    WHERE (mask-expr1) assign-stmt

  Construct form:

    [name :] WHERE (mask-expr1)
       [where-body-stmt]...
    [ELSEWHERE (mask-expr2) [name]
       [where-body-stmt]...]
    [ELSEWHERE [name]
       [where-body-stmt]...]
    END WHERE [name]

    name             Is the name of the WHERE construct.

    mask-expr1       Are logical array expressions (called
    mask-expr2       mask expressions).

    assign-stmt      Is an assignment statement of the form:

                     array variable = array expression

    where-body-stmt  Is one of the following:
                     o An "assign-stmt"
                     o A WHERE statement or construct

  If a construct name is specified in a WHERE statement, the same
  name must appear in the corresponding END WHERE statement.  The
  same construct name can optionally appear in any ELSEWHERE
  statement in the construct.  (ELSEWHERE cannot specify a different
  name.)

  In each assignment statement, the mask expression, the variable
  being assigned to, and the expression on the right side, must all
  be conformable.  Also, the assignment statement cannot be a defined
  assignment.

  Each mask expression in the WHERE construct must be conformable.

  Only the WHERE statement (or the first line of the WHERE construct)
  can be labeled as a branch target statement.

  The following is an example of a WHERE statement:

    INTEGER A, B, C
    DIMENSION A(5), B(5), C(5)
    DATA A /0,1,1,1,0/
    DATA B /10,11,12,13,14/
    C = -1

    WHERE(A .NE. 0) C = B / A

  The resulting array C contains:  -1,11,12,13, and -1.

  The assignment statement is only executed for those elements where
  the mask is true.  Think of the mask expression in this example as
  being evaluated first into a logical array which has the value true
  for those elements where A is positive.

  This array of trues and falses is applied to the arrays A, B and C
  in the assignment statement.  The right side is only evaluated for
  elements for which the mask is true; assignment on the left side is
  only performed for those elements for which the mask is true.  The
  elements for which the mask is false do not get assigned a value.

  In a WHERE construct the mask expression is evaluated first and
  only once.  Every assignment statement following the WHERE is
  executed as if it were a WHERE statement with "mask-expr1" and
  every assignment statement following the ELSEWHERE is executed as
  if it were a WHERE statement with ".NOT.  mask-expr1".  If
  ELSEWHERE specifies "mask-expr2", it is executed as "(.NOT.
  mask-expr1) .AND.  mask-expr2".

  You should be careful if the statements have side effects, or
  modify each other or the mask expression.

  The following is an example of the WHERE construct:

    DIMENSION PRESSURE(1000), TEMP(1000), PRECIPITATION(1000)
    WHERE(PRESSURE .GE. 1.0)
      PRESSURE = PRESSURE + 1.0
      TEMP = TEMP - 10.0
    ELSEWHERE
      PRECIPITATION = .TRUE.
    ENDWHERE

  The mask is applied to the arguments of functions on the right side
  of the assignment if they are considered to be elemental functions.
  Only elemental intrinsics are considered elemental functions.
  Transformational intrinsics, inquiry intrinsics, and functions or
  operations defined in the subprogram are considered to be
  nonelemental functions.

  Consider the following example using LOG, an elemental function:

    WHERE(A .GT. 0)  B = LOG(A)

  The mask is applied to A, and LOG is executed only for the positive
  values of A.  The result of the LOG is assigned to those elements
  of B where the mask is true.

  Consider the following example using SUM, a nonelemental function:

    REAL A, B
    DIMENSION A(10,10), B(10)
    WHERE(B .GT. 0.0)  B = SUM(A, DIM=1)

  Since SUM is nonelemental, it is evaluated fully for all of A.
  Then, the assignment only happens for those elements for which the
  mask evaluated to true.

  Consider the following example:

    REAL A, B, C
    DIMENSION A(10,10), B(10), C(10)
    WHERE(C .GT. 0.0)  B = SUM(LOG(A), DIM=1)/C

  Because SUM is nonelemental, all of its arguments are evaluated
  fully regardless of whether they are elemental or not.  In this
  example, LOG(A) is fully evaluated for all elements in A even
  though LOG is elemental.  Notice that the mask is applied to the
  result of the SUM and to C to determine the right side.  One way of
  thinking about this is that everything inside the argument list of
  a nonelemental function does not use the mask, everything outside
  does.

91  –  WRITE

  Transfers data from internal storage to user-specified external
  logical units (such as disks, printers, terminals, and pipes) or
  internal files.

  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=.

     adv     Specifies advancing (ADVANCE='YES') or nonadvancing
             input (ADVANCE='NO').  The default is 'YES'.

     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.

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

91.1  –  Sequential

91.1.1  –  Formatted

  Formatted sequential WRITE statement format:

     WRITE (extu,fmt [,adv][,err][,iostat]) [iolist]

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

91.1.2  –  List-directed

  List-directed sequential WRITE statement format:

     WRITE (extu,*[,iostat][,err]) [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.

91.1.3  –  Namelist

  Namelist sequential WRITE statement format:

     WRITE (extu,nml[,iostat][,err])

  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.

91.1.4  –  Unformatted

  Unformatted sequential WRITE statement format:

     WRITE (extu[,iostat][,err]) [iolist]

  Writes to a specified external unit.  Does not translate the data.

91.2  –  Direct

91.2.1  –  Formatted

  Formatted direct WRITE statement format:

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

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

91.2.2  –  Unformatted

  Unformatted direct WRITE statement format:

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

  Writes to a specified external unit.  Does not translate the data.

91.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".

91.4  –  Indexed

91.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".

91.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 Help