/sys$common/syshlp/HELPLIB.HLB  —  FORTRAN  Intrinsic Procedures

1  –  ABS

  ABS (number)

  Class:  Elemental function - Generic

  Returns the absolute value of the argument.  The absolute value of
  a complex number, (X,Y), is the real value:

      (X**2 + Y**2)**(1/2).

  +------+----------+----------+------------+-------------+
  | Args | Generic  | Specific |  Argument  | Result Type |
  +------+----------+----------+------------+-------------+
  |  1   |  ABS     |  --      | INTEGER*1  | INTEGER*1   |
  |      |          | IIABS    | INTEGER*2  | INTEGER*2   |
  |      |see note1 | IABS     | INTEGER*4  | INTEGER*4   |
  |      |          | KIABS    | INTEGER*8  | INTEGER*8   |
  |      |          | ABS      | REAL*4     | REAL*4      |
  |      |          | DABS     | REAL*8     | REAL*8      |
  |      |          | QABS     | REAL*16    | REAL*16     |
  |      |see note2 | CABS     | COMPLEX*8  | REAL*4      |
  |      |          | CDABS    | COMPLEX*16 | REAL*8      |
  |      |          | ZABS     | COMPLEX*16 | REAL*8      |
  |      |          | CQABS    | COMPLEX*32 | REAL*16     |
  +------+----------+----------+------------+-------------+

  Note1: Or JIABS.  For compatibility with older versions
         of Fortran, IABS can also be specified as a generic
         function.

  Note2: The setting of compiler options specifying real
         size can affect CABS.

2  –  ACHAR

  ACHAR (integer-number)

  Class:  Elemental function - Generic

  Returns the character in a specified position of the ASCII
  character set, even if the processor's default character set is
  different.  It is the inverse of the IACHAR function.  In HP
  Fortran, ACHAR is equivalent to the CHAR function.

  The result is of type character of length 1 with the kind type
  parameter value of KIND ('A').

  If I has a value within the range 0 to 127, the result is the
  character in position I of the ASCII character set.

3  –  ACOS

  ACOS (real-number)

  Class:  Elemental function - Generic

  Returns the arc cosine of the argument in radians.  The absolute
  value of the argument must be less than or equal to 1.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   | ACOS    | ACOS     | REAL*4     | REAL*4      |
  |      |         | DACOS    | REAL*8     | REAL*8      |
  |      |         | QACOS    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

4  –  ACOSD

  ACOSD (real-number)

  Class:  Elemental function - Generic

  Returns the arccosine of the argument in degrees.  The value of the
  argument must be between 0 (exclusive) and 1 (inclusive).

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  ACOSD  |  ACOSD   | REAL*4     | REAL*4      |
  |      |         |  DACOSD  | REAL*8     | REAL*8      |
  |      |         |  QACOSD  | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

5  –  ADJUSTL

  ADJUSTL (string)

  Class:  Elemental function - Generic

  Adjusts a character string to the left, removing leading blanks and
  inserting trailing blanks.

  The result is of type character with the same length and kind type
  parameter as "string".

6  –  ADJUSTR

  ADJUSTR (string)

  Class:  Elemental function - Generic

  Adjusts a character string to the right, removing trailing blanks
  and inserting leading blanks.

  The result is of type character with the same length and kind type
  parameter as "string".

7  –  AIMAG

  AIMAG (complex-number)

  Class:  Elemental function - Generic

  Returns the imaginary part of a complex number.  If Z has the value
  (x, y), the result has the value "y".  This function can also be
  specified as IMAG.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   | AIMAG   | AIMAG    | COMPLEX*8  | REAL*4      |
  |      |         | DIMAG    | COMPLEX*16 | REAL*8      |
  |      |         | QIMAG    | COMPLEX*32 | REAL*16     |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect AIMAG.

8  –  AINT

  AINT (real-number[,kind])

  Class:  Elemental function - Generic

  Returns the largest integer whose absolute value does not exceed
  the absolute value of the argument and has the same sign as the
  argument.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  AINT   | AINT     | REAL*4     | REAL*4      |
  |      |         | DINT     | REAL*8     | REAL*8      |
  |      |         | QINT     | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

9  –  ALL

  ALL (mask [,dim])

  Class:  Transformational function - Generic

  Determines if all values are true in an entire array or in a
  specified dimension of an array.

  The "mask" must be a logical array.  The "dim" must be a scalar
  integer with a value in the range 1 to n, where "n" is the rank of
  "mask".

  The result is a logical array with the same kind type parameter as
  "mask".  The result is scalar if "dim" is absent or "mask" has rank
  one.  Otherwise, the result is an array with rank that is one less
  than "mask", and shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn),
  where (d1, d2,..., dn) is the shape of "mask".

  The result of ALL (mask) has the value true if all elements of
  "mask" are true or "mask" has size zero.  The result has the value
  false if any element of "mask" is false.

  If "mask" has rank one, ALL (mask, dim) has the same value as ALL
  (mask).  Otherwise, the value of element (s1, s2,..., s"dim"-1,
  s"dim"+1,..., sn) of ALL (mask, dim) is equal to ALL (mask (s1,
  s2,..., s"dim"-1, :, s"dim"+1, ..., sn).

  Examples:

  ALL ((/.TRUE., .FALSE., .TRUE./)) has the value false.

  ALL ((/.TRUE., .TRUE., .TRUE./)) has the value true.

  Consider the following arrays:

    Array A       Array B

    |1 5 7|       |0 5 7|
    |3 6 8|       |2 6 9|

  ALL (A .NE.  B, DIM=1) has the value (true, false, true).

  ALL (A .NE.  B, DIM=2) has the value (true, true).

10  –  ALLOCATED

  ALLOCATED (array)

  Class:  Inquiry function - Generic

  Indicates whether an allocatable array is currently allocated.

  The "array" must be an allocatable array.

  The result has the value true if ARRAY is currently allocated,
  false if ARRAY is not currently allocated, or undefined if its
  allocation status is undefined.

  The setting of integer size compiler options can affect this
  function.

  Example:

  REAL, ALLOCATABLE, DIMENSION (:,:,:) :: E
  PRINT *, ALLOCATED (E)       ! Returns the value false
  ALLOCATE (E (12, 15, 20))
  PRINT *, ALLOCATED (E)       ! Returns the value true

11  –  AMAX0

  See the MAX intrinsic function.

12  –  AMIN0

  See the MIN intrinsic function.

13  –  ANINT

  ANINT (real-number [,kind])

  Class:  Elemental function - Generic

  Returns the value of the integer nearest to the value of the
  argument.

  If real number x is greater than zero, ANINT (x) has the value AINT
  (x + 0.5).  If x is less than or equal to zero, ANINT (x) has the
  value AINT (x - 0.5).

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   | ANINT   | ANINT    | REAL*4     | REAL*4      |
  |      |         | DNINT    | REAL*8     | REAL*8      |
  |      |         | QNINT    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

  See also the NINT intrinsic function.

14  –  ANY

  ANY (mask [,dim])

  Class:  Transformational function - Generic

  Determines if any value is true in an entire array or in a
  specified dimension of an array.

  The "mask" must be a logical array.  The "dim" must be a scalar
  integer with a value in the range 1 to n, where "n" is the rank of
  "mask".

  The result is a logical array with the same kind type parameter as
  "mask".  The result is scalar if "dim" is absent or "mask" has rank
  one.  Otherwise, the result is an array with rank that is one less
  than "mask", and shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn),
  where (d1, d2,..., dn) is the shape of "mask".

  The result of ANY (mask) has the value true if any elements of
  "mask" are true.  The result has the value false if no element of
  "mask" is true or "mask" has size zero.

  If "mask" has rank one, ANY (mask, dim) has the same value as ANY
  (mask).  Otherwise, the value of element (s1, s2,..., s"dim"-1,
  s"dim"+1,..., sn) of ANY (mask, dim) is equal to ANY (mask (s1,
  s2,..., s"dim"-1, :, s"dim"+1, ..., sn).

  Examples:

  ANY ((/.FALSE., .FALSE., .TRUE./)) has the value true.

  Consider the following arrays:

    Array A       Array B

    |1 5 7|       |0 5 7|
    |3 6 8|       |2 6 9|

  ANY (A .NE.  B, DIM=1) has the value (true, false, true).

  ANY (A .NE.  B, DIM=2) has the value (true, true).

15  –  ASIN

  ASIN (real-number)

  Class:  Elemental function - Generic

  Returns the arcsine of the argument in radians.  The absolute value
  of the argument must be less than or equal to 1.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  ASIN   | ASIN     | REAL*4     | REAL*4      |
  |      |         | DASIN    | REAL*8     | REAL*8      |
  |      |         | QASIN    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

16  –  ASIND

  ASIND (real-number)

  Class:  Elemental function - Generic

  Returns the arc sine of the argument in degrees.  The value of the
  argument must be between 0 (exclusive) and 1 (inclusive).

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  |  ASIND  | ASIND    | REAL*4     | REAL*4      |
  |      |         | DASIND   | REAL*8     | REAL*8      |
  |      |         | QASIND   | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

17  –  ASM (Alpha only)

  ASM (character [, any-type-arg])

  Class:  Nonelemental function - Generic

  Lets you use assembler instructions in an executable program.

  The first argument is a character constant or a concatenation of
  character constants containing the assembler instructions.  The
  optional second argument can be of any type.  It can be a source or
  destination argument for the instruction, for example.

  Arguments are passed by value.  If you want to pass an argument by
  reference (for example, a whole array, a character string, or a
  record structure), you can use the %REF built-in function.

  Labels are allowed, but all references must be from within the same
  ASM function.  This lets you set up looping constructs, for
  example.  Cross-jumping between ASM functions is not permitted.

  In general, an ASM function can appear anywhere that an intrinsic
  function can be used.  Since the supplied assembly code, assembly
  directives, or assembly data is integrated into the code stream,
  the compiler may choose to use different registers, better code
  sequences, and so on, just as if the code were written in Fortran.

  You do not have absolute control over instruction sequences and
  registers, and the compiler may intersperse other code together
  with the ASM code for better performance.  Better code sequences
  may be substituted by the optimizer if it chooses to do so.

  Only register names beginning with a dollar sign ($) or percent
  sign (%) are permitted.  For more information on register name
  conventions, see the OpenVMS operating system documentation set.

    +---------+-------------------+-------------+
    | Generic | Specific          | Result Type |
    +---------+-------------------+-------------+
    |  ASM    | ASM (see Note1)   | INTEGER*8   |
    |         | FASM (see Note2)  | REAL*4      |
    |         | DASM (see Note2)  | REAL*8      |
    +---------+-------------------+-------------+

  Note1: The value must be stored in register $0 by the user code.
  Note2: The value must be stored in register $F0 by the user code.

  Example:

  Consider the following:

   ! Concatenation is recommended for clarity.
   ! Notice that ";" separates instructions.
   !
   nine=9

   type *, asm('addq %0, $17, $0;'//  ! Adds the first two arguments
    1    'ldq $22, %6;'//             !   and puts the answer in
    1    'ldq $23, %7;'//             !   register $0
    1    'ldq $24, %8;'//             !
    1    'mov $0, %fp;'//             ! Comments are not allowed in the
    1    'addq $18, %fp, $0;'//       !   constant, but are allowed here
    1     'addq $19, $0, $0;'//
    1     'addq $20, $0, $0;'//
    1     'addq $21, $0, $0;'//
    1     'addq $22, $0, $0;'//
    1     'addq $23, $0, $0;'//
    1    'addq $24, $0, $0;',
    1 1,2,3,4,5,6,7,8,nine)           ! The actual arguments to the
                                      !   ASM (usually by value)
   end

  This example shows an integer ASM function that adds up 9 values
  and returns the sum as its result.  Note that the user stores the
  function result in register $0.

  All arguments are passed by value.  The arguments not passed in
  registers can be named %6, %7, and %8, which correspond to the
  actual arguments 7, 8, and 9 (since %0 is the first argument).
  Notice that you can reference reserved registers like %fp.

  The compiler creates the appropriate argument list.  So, in this
  example, the first argument value (1) will be available in register
  $16, and the eighth argument value (8) will be available in %7,
  which is actually 8($30).

18  –  ASSOCIATED

  ASSOCIATED (pointer [,target])

  Class:  Inquiry function - Generic

  Returns the association status of its pointer argument or indicates
  whether the pointer is associated with the target.  The pointer
  must not have an undefined association status.

  The "target" can be a pointer or target.

  If only POINTER appears, the result is true if it is currently
  associated with a target; otherwise, the result is false.

  If TARGET also appears and is a target, the result is true if
  POINTER is currently associated with TARGET; otherwise, the result
  is false.

  If TARGET is a pointer, the result is true if both POINTER and
  TARGET are currently associated with the same target; otherwise,
  the result is false.  (If either POINTER or TARGET is
  disassociated, the result is false.)

  The setting of integer size compiler options can affect this
  function.

  Examples:

  Consider the following:

     REAL, TARGET, DIMENSION (0:50) :: TAR
     REAL, POINTER, DIMENSION (:) :: PTR
     PTR => TAR
     PRINT *, ASSOCIATED (PTR, TAR)    ! Returns the value true

  The subscript range for PTR is 0:50.  Consider the following
  pointer assignment statements:

     (1) PTR => TAR (:)
     (2) PTR => TAR (0:50)
     (3) PTR => TAR (0:49)

  For statements 1 and 2, ASSOCIATED (PTR, TAR) is true because TAR
  has not changed (the subscript range for PTR in both cases is 1:51,
  following the rules for deferred-shape arrays).  For statement 3,
  ASSOCIATED (PTR, TAR) is false because the upper bound of PTR has
  changed.

  Consider the following:

     REAL, POINTER, DIMENSION (:) :: PTR2, PTR3
     ALLOCATE (PTR2 (0:15))
     PTR3 => PTR2
     PRINT *, ASSOCIATED (PTR2, PTR3)   ! Returns the value true
     ...
     NULLIFY (PTR2)
     NULLIFY (PTR3)
     PRINT *, ASSOCIATED (PTR2, PTR3)   ! Returns the value false

19  –  ATAN

  ATAN (real-number)

  Class:  Elemental function - Generic

  Returns the arc tangent of the argument in radians.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |   ATAN  | ATAN     | REAL*4     | REAL*4      |
  |      |         | DATAN    | REAL*8     | REAL*8      |
  |      |         | QATAN    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

20  –  ATAND

  ATAND (real-number)

  Class:  Elemental function - Generic

  Returns the arc tangent of the argument in degrees.  The value of
  the argument must be greater than 0.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  |  ATAND  | ATAND    | REAL*4     | REAL*4      |
  |      |         | DATAND   | REAL*8     | REAL*8      |
  |      |         | QATAND   | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

21  –  ATAN2

  ATAN2 (real-number, real-number)

  Class:  Elemental function - Generic

  Returns the arc tangent of the quotient of the two arguments in
  radians.  If both arguments are zero, the result is undefined.  If
  the first argument is positive, the result is positive.  If the
  first argument is negative, the result is negative.  If the first
  argument is zero, the result is zero.  If the second argument is
  zero, the absolute value of the result is pi/2.

  The range of the result is -pi < result <= pi.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  ATAN2  | ATAN2    | REAL*4     | REAL*4      |
  |      |         | DATAN2   | REAL*8     | REAL*8      |
  |      |         | QATAN2   | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

22  –  ATAN2D

  ATAN2D (real-number, real-number)

  Class:  Elemental function - Generic

  Returns the arc tangent of the quotient of the two arguments in
  degrees.

  If both arguments are zero, the result is undefined.  If the first
  argument is positive, the result is positive.  If the first
  argument is negative, the result is negative.  If the first
  argument is zero, the result is zero.  If the second argument is
  zero, the absolute value of the result is 90 degrees.  The value of
  the argument must be greater than zero.

  The range of the result is -180 degrees < result <= 180 degrees.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   2  | ATAN2D  | ATAN2D   | REAL*4     | REAL*4      |
  |      |         | DATAN2D  | REAL*8     | REAL*8      |
  |      |         | QATAN2D  | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

23  –  BIT_SIZE

  BIT_SIZE (integer)

  Class:  Inquiry function - Generic

  Returns the number of bits in an integer type.

  The result value is the number of bits ("s") defined by the bit
  model for integers with the kind type parameter of the argument.
  For information on the bit model, see the HP Fortran for OpenVMS
  Language Reference Manual.

  Example:

  BIT_SIZE (1_2) has the value 16 because the INTEGER*2 type contains
  16 bits.

24  –  BTEST

  BTEST (integer, position)

  Class:  Elemental function - Generic

  Returns a logical value of true if the bit within the integer
  specified by position is set to 1 (bit test).  The low-order bit is
  position 0.

  +------+---------+----------------+------------+-------------+
  | Args | Generic | Specific       |  Argument  | Result Type |
  +------+---------+----------------+------------+-------------+
  |   2  |         |   --           | INTEGER*1  | LOGICAL*4   |
  |      |         | BITEST         | INTEGER*2  | LOGICAL*2   |
  |      |  BTEST  | BTEST(see note)| INTEGER*4  | LOGICAL*4   |
  |      |         | BKTEST         | INTEGER*8  | LOGICAL*8   |
  +------+---------+----------------+------------+-------------+

  NOTE: Or BJTEST

25  –  CEILING

  CEILING (real-number [,KIND])

  Class:  Elemental function - Generic

  Returns the smallest integer greater than or equal to its argument.

  The result is of type default integer (unless KIND specifies a
  different integer KIND).  The value of the result is equal to the
  smallest integer greater than or equal to the real-number.  The
  result is undefined if the value cannot be represented in the
  default integer range.

26  –  CHAR

  CHAR (integer [,kind])

  Class:  Elemental function - Generic

  Returns the character in the specified position of the processor's
  character set.  It is the inverse of the function ICHAR.

  The input value must be in the range 0 to n - 1, where "n" is the
  number of characters in the processor's character set.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |   --    |  --      | INTEGER*1  | CHARACTER   |
  |      |         |  --      | INTEGER*2  | CHARACTER   |
  |      |         |  CHAR    | INTEGER*4  | CHARACTER   |
  |      |         |  --      | INTEGER*8  | CHARACTER   |
  +------+---------+----------+------------+-------------+

  This function cannot be passed as an actual argument.

27  –  CMPLX

  CMPLX (number [,number] [,kind])

  Class:  Elemental function - Generic

  Converts the argument(s) into a complex value.

  If one argument is specified, the argument is converted into the
  real part of the complex value and the imaginary part becomes zero.
  If two arguments are specified, the first argument is converted
  into the real part of the complex value and the second argument is
  converted into the imaginary part of the complex value.  If two
  arguments are specified, they must have the same data type.

  The setting of compiler options specifying real size can affect
  this function.

  +-------+---------+----------+------------+-------------+
  | Args  | Generic | Specific |  Argument  | Result Type |
  +-------+---------+----------+------------+-------------+
  | 1,2   |  CMPLX  | CMPLX    | INTEGER*2  | COMPLEX*8   |
  | 1,2   |         | CMPLX    | INTEGER*4  | COMPLEX*8   |
  | 1,2   |         | CMPLX    | REAL*4     | COMPLEX*8   |
  | 1,2   |         | CMPLX    | REAL*8     | COMPLEX*8   |
  | 1,2   |         | CMPLX    | REAL*16    | COMPLEX*8   |
  |  1    |         | CMPLX    | COMPLEX*8  | COMPLEX*8   |
  |  1    |         | CMPLX    | COMPLEX*16 | COMPLEX*8   |
  +-------+---------+----------+------------+-------------+

  This function cannot be passed as an actual argument.

28  –  CONJG

  CONJG (complex-number)

  Class:  Elemental function - Generic

  Returns the complex conjugate of the argument.  If the argument is
  (X,Y), its complex conjugate is (X,-Y).

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  |  CONJG  | CONJG    | COMPLEX*8  | COMPLEX*8   |
  |      |         | DCONJG   | COMPLEX*16 | COMPLEX*16  |
  |      |         | QCONJG   | COMPLEX*32 | COMPLEX*32  |
  +------+---------+----------+------------+-------------+

29  –  COS

  COS (number)

  Class:  Elemental function - Generic

  Returns the cosine of the argument.  The argument must be in
  radians; it is treated modulo 2*pi.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  |  COS    | COS      | REAL*4     | REAL*4      |
  |      |         | DCOS     | REAL*8     | REAL*8      |
  |      |         | QCOS     | REAL*16    | REAL*16     |
  |      |see note | CCOS     | COMPLEX*8  | COMPLEX*8   |
  |      |         | CDCOS    | COMPLEX*16 | COMPLEX*16  |
  |      |         | ZCOS     | COMPLEX*16 | COMPLEX*16  |
  |      |         | CQCOS    | COMPLEX*32 | COMPLEX*32  |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect CCOS.

30  –  COSD

  COSD (number)

  Class:  Elemental function - Generic

  Returns the cosine of the argument.  The argument must be in
  degrees; it is treated modulo 360.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |   COSD  | COSD     | REAL*4     | REAL*4      |
  |      |         | DCOSD    | REAL*8     | REAL*8      |
  |      |         | QCOSD    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

31  –  COSH

  COSH (real-number)

  Class:  Elemental function - Generic

  Returns the hyperbolic cosine of the argument.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  | COSH    | COSH     | REAL*4     | REAL*4      |
  |      |         | DCOSH    | REAL*8     | REAL*8      |
  |      |         | QCOSH    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

32  –  COTAN

  COTAN (real-number)

  Class:  Elemental function - Generic

  Returns the cotangent of the argument.

  The argument cannot be zero.  It must be in radians and is treated
  as modulo 2*pi.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |   1  | COTAN   | COTAN    | REAL*4     | REAL*4      |
  |      |         | DCOTAN   | REAL*8     | REAL*8      |
  |      |         | QCOTAN   | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

33  –  COTAND

  COTAND (real-number)

  Class:  Elemental function - Generic

  Returns the cotangent of the argument.  The argument must be in
  degrees; it is treated modulo 360.

  +------+----------+----------+------------+-------------+
  | Args | Generic  | Specific |  Argument  | Result Type |
  +------+----------+----------+------------+-------------+
  |  1   |  COTAND  | COTAND   | REAL*4     | REAL*4      |
  |      |          | DCOTAND  | REAL*8     | REAL*8      |
  |      |          | QCOTAND  | REAL*16    | REAL*16     |
  +------+----------+----------+------------+-------------+

34  –  COUNT

  COUNT (mask [,dim] [,kind])

  Class:  Transformational function - Generic

  Counts the number of true elements in an entire array or in a
  specified dimension of an array.

  The "mask" must be a logical array.  The "dim" must be a scalar
  integer with a value in the range 1 to n, where "n" is the rank of
  "mask".  The "kind" must be a scalar integer initialization
  expression.

  The result is integer.  If "kind" is present, the kind parameter of
  the result is that specified by "kind"; otherwise, the kind
  parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  The result is a scalar if "dim" is absent or "mask" has rank one.
  Otherwise, the result is an array with rank that is one less than
  "mask", and shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn), where
  (d1, d2,..., dn) is the shape of "mask".

  The result of COUNT (mask) is a value equal to the number of true
  elements of "mask".  If mask has size zero, the result is zero.

  If "mask" has rank one, COUNT (mask, dim) has the same value as
  COUNT (mask).  Otherwise, the value of element (s1, s2,...,
  s"dim"-1, s"dim"+1,..., sn) of COUNT (mask, dim) is equal to COUNT
  (mask (s1, s2,..., s"dim"-1, :, s"dim"+1, ...,sn).

  Examples:

  COUNT ((/.TRUE., .FALSE., .TRUE./)) has the value 2.

  COUNT ((/.TRUE., .TRUE., .TRUE./)) has the value 3.

  Consider the following arrays:

    Array A       Array B

    |1 5 7|       |0 5 7|
    |3 6 8|       |2 6 9|

  COUNT (A .NE.  B, DIM=1) has the value (2, 0, 1).

  COUNT (A .NE.  B, DIM=2) has the value (1, 2).

35  –  CPU_TIME

  CPU_TIME (time)

  Class:  Subroutine

  Returns a processor-dependent approximation of the processor time
  (in seconds).

  Argument "time" must be scalar and of real type.  It is an
  INTENT(OUT) argument.

  If a meaningful time cannot be returned, a processor-dependent
  negative value is returned.

  Example:

    REAL time_begin, time_end
    ...
    CALL CPU_TIME(time_begin)
    ...                         !some operation coding
    CALL CPU_TIME(time_end)
    PRINT (*,*) 'Time of operation was ', time_begin - time_end, ' seconds'

36  –  CSHIFT

  CSHIFT (array, shift [,dim])

  Class:  Transformational function - Generic

  Performs a circular shift on a rank-one array, or performs circular
  shifts on all the complete rank-one sections along a given
  dimension of an array of rank two or greater.

  Elements shifted off one end are inserted at the other end.
  Different sections can be shifted by different amounts and in
  different directions.

  The "shift" can be a scalar integer or array with rank one less
  than "array".  The "dim" must be a scalar integer with a value in
  the range 1 to n, where "n" is the rank of "array".  If "dim" is
  omitted, it is assumed to be 1.

  The result is an array with the same type, type parameters, and
  shape as "array".

  If "array" has rank one, element i of the result is array (1 +
  MODULO (i + "shift" - 1, SIZE (array))).

  If "array" has rank greater than 1, section (s1, s2, ...s"dim"-1,
  :, s"dim"+1, ..., sn) of the result has a value equal to CSHIFT
  (array(s1, s2, ..., s"dim"-1, :, s"dim"+1, ..., sn), sh, 1), where
  "sh" is "shift" or shift(s1, s2, ..., s"dim"-1, s"dim"+1,..., sn).

  The value of "shift" determines the amount and direction of the
  circular shift.  A positive integer causes a shift to the left (in
  rows) or up (in columns).  A negative integer causes a shift to the
  right (in rows) or down (in columns).

  Examples:

  V is the array (1, 2, 3, 4, 5, 6).

  CSHIFT (V, SHIFT=2) shifts V circularly to the left by 2 positions,
  producing the value (3, 4, 5, 6, 1, 2).

  CSHIFT (V, SHIFT= -2) shifts V circularly to the right by 2
  positions, producing the value (5, 6, 1, 2, 3, 4).

  M is the array Consider the following array:

    Array M

    |1 2 3|
    |4 5 6|
    |7 8 9|

  CSHIFT (M, SHIFT = 1, DIM = 2) produces the result:

    |2 3 1|
    |5 6 4|
    |8 9 7|

  CSHIFT (M, SHIFT = -1, DIM = 1) produces the result

    |7 8 9|
    |1 2 3|
    |4 5 6|

  CSHIFT (M, SHIFT = (/1, -1, 0/), DIM = 2) produces the result

    |2 3 1|
    |6 4 5|
    |7 8 9|

37  –  DATE

  DATE (buf)

  Class:  Subroutine

  Returns the current date as set within the system.  The date is
  returned as a 9-byte ASCII character string as follows:

    dd-mmm-yy

  The "buf" is a 9-byte variable, array, array element, or character
  substring.  If "buf" is numeric type and smaller than 9 bytes, data
  corruption can occur.

  If "buf" is character type, its associated length is passed to the
  subroutine.  If "buf" is smaller than 9 bytes, the subroutine
  truncates the date to fit in the specified length.  If a CHARACTER
  array is passed, the subroutine stores the date in the first array
  element, using the element length, not the length of the entire
  array.  For example, consider the following:

  CHARACTER*1 DAY(9)
  ...
  CALL DATE(DAY)

  The length of the first array element in CHARACTER array DAY is
  passed to the DATE subroutine.  The subroutine then truncates the
  date to fit into the one-character element, producing an incorrect
  result.

38  –  DATE_AND_TIME

  DATE_AND_TIME ([date] [,time] [,zone] [,values])

  Class:  Subroutine

  Returns character data on the real-time clock and date in a form
  compatible with the representations defined in Standard ISO
  8601:1988.

  Optional arguments (all are INTENT(OUT)):

   o  The "date" must be scalar and of type default character; its
      length must be at least 8 to contain the complete value.  Its
      leftmost 8 characters are set to a value of the form CCYYMMDD,
      where:

        CC is the century
        YY is the year within the century
        MM is the month within the year
        DD is the day within the month

   o  The "time" must be scalar and of type default character; its
      length must be at least 10 to contain the complete value.  Its
      leftmost 10 characters are set to a value of the form
      hhmmss.sss, where:

        hh is the hour of the day
        mm is the minutes of the hour
        ss.sss is the seconds and milliseconds of the minute

   o  The "zone" must be scalar and of type default character; its
      length must be at least 5 to contain the complete value.  Its
      leftmost 5 characters are set to a value of the form + or -
      hhmm, where "hh" and "mm" are the time difference with respect
      to Coordinated Universal Time (UTC) in hours and parts of an
      hour expressed in minutes, respectively.

   o  The "values" must be of type default integer and of rank one.
      Its size must be at least 8.  The values returned in "values"
      are as follows:

        values (1) is the 4-digit year
        values (2) is the month of the year
        values (3) is the day of the month
        values (4) is the time difference with respect to
                   Coordinated Universal Time (UTC) in minutes
        values (5) is the hour of the day (range 0 to 23)
        values (6) is the minutes of the hour (range 0 to 59).
        values (7) is the seconds of the minute (range 0 to 59).
        values (8) is the milliseconds of the second (range 0 to 999).

      VALUES (5) through (8) are in local time.

  Example:

  Consider the following example executed on 2000 March 28 at
  11:04:14.5:

  INTEGER DATE_TIME (8)
  CHARACTER (LEN = 12) REAL_CLOCK (3)
  CALL DATE_AND_TIME (REAL_CLOCK (1), REAL_CLOCK (2), &
                      REAL_CLOCK (3), DATE_TIME)

  This assigns the value "20000328" to REALCLOCK (1), the value
  "110414.500" to REALCLOCK (2), and the value "-0500" to REALCLOCK
  (3).  The following values are assigned to DATETIME:  2000, 3, 28,
  -300, 11, 4, 14, and 500.

39  –  DBLE

  DBLE (number)

  Class:  Elemental function - Generic

  Converts a number into a REAL*8 value.

  +------+-----------+----------+------------+-------------+
  | Args | Generic   | Specific |  Argument  | Result Type |
  +------+-----------+----------+------------+-------------+
  |  1   |  DBLE     |   --     | INTEGER*1  | REAL*8      |
  |      |           |   --     | INTEGER*2  | REAL*8      |
  |      |           |   --     | INTEGER*4  | REAL*8      |
  |      |           |   --     | INTEGER*8  | REAL*8      |
  |      |           |  DBLE    | REAL*4     | REAL*8      |
  |      |           |   --     | REAL*8     | REAL*8      |
  |      |           |  DBLEQ   | REAL*16    | REAL*8      |
  |      |           |   --     | COMPLEX*8  | REAL*8      |
  |      |           |   --     | COMPLEX*16 | REAL*8      |
  |      |           |   --     | COMPLEX*32 | REAL*8      |
  +------+-----------+----------+------------+-------------+

  These functions cannot be passed as actual arguments.

40  –  DCMPLX

  DCMPLX (number [,number])

  Class:  Elemental function - Generic

  Converts the argument(s) into a double complex value.

  If one argument is specified, the argument is converted into the
  real part of the complex value and the imaginary part becomes zero.
  If two arguments are specified, the first argument is converted
  into the real part of the complex value and the second argument is
  converted into the imaginary part of the complex value.  If two
  arguments are specified, they must have the same data type.

  +-------+----------+----------+------------+-------------+
  | Args  | Generic  | Specific |  Argument  | Result Type |
  +-------+----------+----------+------------+-------------+
  | 1,2   | DCMPLX   |   --     | INTEGER*1  | COMPLEX*16  |
  | 1,2   |          |   --     | INTEGER*2  | COMPLEX*16  |
  | 1,2   |          |   --     | INTEGER*4  | COMPLEX*16  |
  | 1,2   |          |   --     | INTEGER*8  | COMPLEX*16  |
  | 1,2   |          |   --     | REAL*4     | COMPLEX*16  |
  | 1,2   |          |   --     | REAL*8     | COMPLEX*16  |
  | 1,2   |          |   --     | REAL*16    | COMPLEX*16  |
  |  1    |          |   --     | COMPLEX*8  | COMPLEX*16  |
  |  1    |          |   --     | COMPLEX*16 | COMPLEX*16  |
  +-------+----------+----------+------------+-------------+

  This function cannot be passed as an actual argument.

41  –  DFLOAT

  DFLOAT (integer)

  Class:  Elemental function - Generic

  Converts an integer into a double precision value.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  DFLOAT |   --     | INTEGER*1  | REAL*8      |
  |      |         | DFLOTI   | INTEGER*2  | REAL*8      |
  |      |         | DFLOTJ   | INTEGER*4  | REAL*8      |
  |      |         | DFLOTK   | INTEGER*8  | REAL*8      |
  +------+---------+----------+------------+-------------+

  These functions cannot be passed as actual arguments.

42  –  DIGITS

  DIGITS (number)

  Class:  Inquiry function - Generic

  Returns the number of significant binary digits for numbers of
  the same type and kind type parameter as the argument.  The
  argument can be an integer or real number (scalar or array
  valued).

  The result is type default integer.

  The models for integer and real numbers are described in the
  HP Fortran for OpenVMS Language Reference Manual.

  Example:

  If X is of type REAL*4, DIGITS (X) has the value 24.

43  –  DIM

  DIM (number, number)

  Class:  Elemental function - Generic

  Returns the value of the first argument minus the minimum (MIN) of
  the two arguments.

  +------+----------+----------+------------+-------------+
  | Args | Generic  | Specific |  Argument  | Result Type |
  +------+----------+----------+------------+-------------+
  |   2  |          |   --     | INTEGER*1  | INTEGER*1   |
  |      |          | IIDIM    | INTEGER*2  | INTEGER*2   |
  |      |see note  | IDIM     | INTEGER*4  | INTEGER*4   |
  |      |          | KIDIM    | INTEGER*8  | INTEGER*8   |
  |      |          | DIM      | REAL*4     | REAL*4      |
  |      |          | DDIM     | REAL*8     | REAL*8      |
  |      |          | QDIM     | REAL*16    | REAL*16     |
  +------+----------+----------+------------+-------------+

  NOTE: Or JIDIM

44  –  DIMAG

  See the AIMAG function.

45  –  DOT_PRODUCT

  DOT_PRODUCT (vector-a, vector-b)

  Class:  Transformational function - Generic

  The "vector"s are rank-one arrays of integer, real, complex, or
  logical type.

  The result is a scalar; its type depends on "vector"s.

  If "vector-a" is of type integer or real, the result value is SUM
  (vector-a * vector-b).

  If "vector-a" is of type complex, the result value is SUM (CONJG
  (vector-a) * vector-b).

  If "vector-a" is of type logical, the result has the value ANY
  (vector-a .AND.  vector-b).

  If either rank-one array has size zero, the result is zero if the
  array is of numeric type, and false if the array is of logical
  type.

  Examples:

  DOT_PRODUCT ((/1, 2, 3/), (/3, 4, 5/)) has the value 26 (calculated
  as follows:

    ((1 x 3) + (2 x 4) + (3 x 5)) = 26)

  DOT_PRODUCT ((/ (1.0, 2.0), (2.0, 3.0) /), (/ (1.0, 1.0), ((1.0,
  4.0) /))) has the value (17.0, 4.0).

  DOT_PRODUCT ((/ .TRUE., .FALSE.  /), (/ .FALSE., .TRUE.  /)) has
  the value false.

46  –  DPROD

  DPROD (real4-number, real4-number)

  Class:  Elemental function - Specific

  Returns the product of two REAL*4 values as a REAL*8 value.

  This function cannot be passed as an actual argument.

47  –  DREAL

  DREAL (dbl-complex-number)

  Class:  Elemental function - Specific

  Converts the real part of a double complex argument to double
  precision type.

48  –  EOF

  EOF (integer)

  Class:  Inquiry function - Generic

  Checks whether a file is at or beyond the end-of-file record.

  The argument represents a unit specifier corresponding to an open
  file.  It cannot be zero unless you have reconnected unit zero to a
  unit other than the screen or keyboard.

  The value of the result is .TRUE.  if the file connected to A is at
  or beyond the end-of-file record; otherwise, .FALSE..

  This function cannot be passed as an actual argument.

  Examples:

  Consider the following:

  !  Creates a file of random numbers, reads them back
        REAL x, total
        INTEGER count
        OPEN (1, FILE = 'TEST.DAT')
        DO I = 1, 20
          CALL RANDOM_NUMBER(x)
          WRITE (1, '(F6.3)') x * 100.0
        END DO
        CLOSE(1)
        OPEN (1, FILE = 'TEST.DAT')
        DO WHILE (.NOT. EOF(1))
          count = count + 1
          READ (1, *) value
          total = total + value
        END DO
  100   IF ( count .GT. 0) THEN
          WRITE (*,*) 'Average is: ', total / count
        ELSE
          WRITE (*,*) 'Input file is empty '
        END IF
         STOP
        END

49  –  EOSHIFT

  EOSHIFT (array, shift [,boundary] [,dim])

  Class:  Transformational function - Generic

  Performs an end-off shift on a rank-one array, or performs end-off
  shifts on all the complete rank-one sections along a given
  dimension of an array of rank two or greater.

  Elements are shifted off at one end of a section and copies of a
  boundary value are filled in at the other end.  Different sections
  can have different boundary values and can be shifted by different
  amounts and in different directions.

  The "array" can be of any type.

  The "shift" can be a scalar integer or an array with a rank that is
  one less than "array", and shape (d1, d2,..., d"dim"-1,
  d"dim"+1,..., dn), where (d1, d2,..., dn) is the shape of "array".

  The "boundary" must be of the same type and kind type parameter as
  "array".  It can be a scalar or an array with a shape that is one
  less than that of "array" and shape (d1, d2,..., d"dim"-1,
  d"dim"+1,..., dn).  If "boundary is omitted, it is assumed to have
  the following values:

    "array" type       "boundary" value
    ------------       ----------------
     integer            0
     real               0.0
     complex            (0.0, 0.0)
     logical            false
     character (len)    "len" blanks

  The "dim" must be a scalar integer with a value in the range 1 to
  n, where "n" is the rank of "array".  If omitted, it is assumed to
  be 1.

  The result is an array with the same type, kind type parameter, and
  shape as "array"

  The value of "shift" determines the amount and direction of the
  end-off shift.  A positive integer causes a shift to the left (in
  rows) or up (in columns).  If an element is shifted off the
  beginning of a vector, the "boundary" value is placed at the end of
  the vector.

  A negative integer causes a shift to the right (in rows) or down
  (in columns).  If an element is shifted off the end of a vector,
  the "boundary" value is placed at the beginning of the vector.

  Examples:

  Consider that V is the array (1, 2, 3, 4, 5, 6).

  EOSHIFT (V, SHIFT=2) shifts the array to the left by 2 positions,
  producing the value (3, 4, 5, 6, 0, 0).

  EOSHIFT (V, SHIFT= -3, BOUNDARY= 99) shifts the array to the right
  by 3 positions, and uses the boundary value of 99, producing the
  value (99, 99, 99, 1, 2, 3).

  Consider that M is the following array:

   |1 2 3|
   |4 5 6|
   |7 8 9|

  EOSHIFT (M, SHIFT = 1, BOUNDARY = '*', DIM=2) produces the result:

   |2 3 *|
   |5 6 *|
   |8 9 *|

  EOSHIFT (M, SHIFT = -1, DIM = 1) produces the result:

   |0 0 0|
   |1 2 3|
   |4 5 6|

  EOSHIFT (M, SHIFT = (/1, -1, 0/), BOUNDARY = (/ '*', '?', '/' /),
  DIM=2) produces the result:

   |2 3 *|
   |? 4 5|
   |7 8 9|

50  –  EPSILON

  EPSILON (real)

  Class:  Inquiry function - Generic

  Returns a positive model number that is almost negligible compared
  to unity in the model representing real numbers.  The argument can
  be scalar or array valued.

  The model for real numbers is described in the HP Fortran for
  OpenVMS Language Reference Manual.

  Example:

  If X is REAL*4 type, EPSILON (X) has the value 2**-23.

51  –  ERRSNS

  ERRSNS ([io-err] [,sys-err] [,stat] [,unit] [,cond])

  Class:  Subroutine

  Returns information about the last Fortran error that occurred.
  The arguments are all return values and must be defined as integer
  variables or array elements:

     io-err    Stores the most recent Fortran error number
               that occurred during program execution.
               The value is zero if no error has occurred.

     sys-err   Stores the most recent RMS STS status code.

     stat      Stores the most recent RMS STV status value.
               This status value provides additional status
               information.

     unit      Stores the logical unit number (if the last
               the last error was an I/O error).

     cond      Stores the actual processor value.  This
               value is always zero.

  If you specify INTEGER*2 arguments, only the low-order 16 bits of
  information are returned or adjacent data can be overwritten.
  Because of this, it is best to use INTEGER*4 arguments.

  The saved error information is set to zero after each call to
  ERRSNS.

52  –  EXIT

  EXIT ([exit-status])

  Class:  Subroutine

  Terminates the program, closes all files, and returns control to
  the operating system.  The optional argument specifies the
  exit-status value of the program.

53  –  EXP

  EXP (exponent)

  Class:  Elemental function - Generic

  Returns e**X, where X is the value of the argument.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  EXP    | EXP      | REAL*4     | REAL*4      |
  |      |         | DEXP     | REAL*8     | REAL*8      |
  |      |         | QEXP     | REAL*16    | REAL*16     |
  |      |see note | CEXP     | COMPLEX*8  | COMPLEX*8   |
  |      |         | CDEXP    | COMPLEX*16 | COMPLEX*16  |
  |      |         | ZEXP     | COMPLEX*16 | COMPLEX*16  |
  |      |         | CQEXP    | COMPLEX*32 | COMPLEX*32  |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect CEXP.

54  –  EXPONENT

  EXPONENT (real-number)

  Class:  Elemental function - Generic

  Returns the exponent part of the argument when represented as a
  model number.

  The result is of type default integer.  If the argument is not
  equal to zero, the result value is the exponent part of the
  argument.  The exponent must be within default integer range;
  otherwise, the result is undefined.

  If the argument is zero, the exponent of the argument is zero.
  For more information on the exponent part in the real model, see
  the HP Fortran for OpenVMS Language Reference Manual.

  Examples:

  EXPONENT (2.0) has the value 2.

  If 4.1 is a REAL*4 value, EXPONENT (4.1) has the value 3.

55  –  FLOAT

  See the REAL function.

56  –  FLOOR

  FLOOR (real-number [,KIND])

  Class:  Elemental function - Generic

  Returns the greatest integer less than or equal to its argument.

  The result is of type default integer (unless KIND specifies a
  different integer KIND).  The result value is equal to the greatest
  integer less than or equal to the argument.  The result is
  undefined if the value cannot be represented in the default integer
  range.

  Examples:

  FLOOR (4.8) has the value 4.

  FLOOR (-5.6) has the value -6.

57  –  FP_CLASS

  FP_CLASS (real-number)

  Class:  Elemental function - Generic

  Returns the class of an IEEE real (S_floating, T_floating, or
  X_floating) argument.

  The result is of type default integer.

  The return values are defined in module "FORSYSDEF".  For
  information on the location of this file, see the HP Fortran for
  OpenVMS User Manual.

  Example:

  FP_CLASS (4.0_8) has the value 4 (FOR_K_FP_POS_NORM, a normal
  positive number).

58  –  FRACTION

  FRACTION (real-number)

  Class:  Elemental function - Generic

  Returns the fractional part of the model representation of the
  argument value.

  The result type is the same as the argument.  The real model is
  described in the HP Fortran for OpenVMS Language Reference Manual.

  Example:

  If 3.0 is a REAL*4 value, FRACTION (3.0) has the value 0.75.

59  –  FREE

  FREE (integer)

  Class:  Intrinsic subroutine

  Frees a block of memory that is currently allocated.

  The argument must be of type INTEGER*8.  This value is the starting
  address of the memory to be freed, previously allocated by the
  MALLOC intrinsic function.

  If the freed address was not previously allocated by MALLOC, or if
  an address is freed more than once, results are unpredictable.

  Examples:

  Consider the following:

  INTEGER(4) ADDR, SIZE
  SIZE = 1024                 ! Size in bytes
  ADDR = MALLOC(SIZE)         ! Allocate the memory
  CALL FREE(ADDR)             ! Free it
  END

60  –  HUGE

  HUGE (number)

  Class:  Inquiry function - Generic

  Returns the largest number in the model representing the same type
  and kind type parameter as the argument.

  The argument can be integer or real; it can be scalar or array
  valued.  The result type is scalar of the same type and kind type
  parameter as the argument.  The integer and real models are
  described in the HP Fortran for OpenVMS Language Reference Manual.

  Example:

  If X is REAL*4 type, HUGE (X) has the value (1 - 2**-24) x 2**128.

61  –  IABS

  See the ABS function.

62  –  IACHAR

  IACHAR (character)

  Class:  Elemental function - Generic

  Returns the position of a character in the ASCII character set,
  even if the processor's default character set is different.  In
  VSI Fortran, IACHAR is equivalent to the ICHAR function.

  The argument must have a length of 1.  The result is of type
  default integer.

63  –  IAND

  IAND (integer, integer)

  Class:  Elemental function - Generic

  Performs a logical AND of the arguments on a bit by bit basis
  (bitwise AND).  This function can also be specified as AND.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  IAND   |  --      | INTEGER*1  | INTEGER*1   |
  |      |         | IIAND    | INTEGER*2  | INTEGER*2   |
  |      |         | JIAND    | INTEGER*4  | INTEGER*4   |
  |      |         | KIAND    | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

64  –  IARGCOUNT

  IARGCOUNT ()

  Class:  Inquiry function - Specific

  Returns the count of actual arguments passed to the current
  routine.  The result is of type default integer.  Functions with a
  type of CHARACTER, COMPLEX(KIND=8), REAL(KIND=16), and
  COMPLEX(KIND=16) have an extra argument added that is used to
  return the function value.

  Formal (dummy) arguments that can be omitted must be declared
  VOLATILE.

  Formal arguments of type CHARACTER cannot be omitted.  Formal
  arguments that are adjustable arrays cannot be omitted.

  The standard way to pass and detect omitted arguments is to use the
  Fortran 95 features of OPTIONAL arguments and the PRESENT intrinsic
  function. Note that a declaration must be visible within the
  calling routine.

  The following example shows the IARGCOUNT intrinsic:

     CALL SUB (A,B)
     ...
     SUBROUTINE SUB (X,Y,Z)
     VOLATILE Z
     TYPE *, IARGCOUNT()       ! Displays the value 2

65  –  IARGPTR

  IARGPTR ()

  Class:  Inquiry function - Specific

  Returns a pointer to the actual argument list for the current
  routine.  IARGPTR takes no arguments and returns an INTEGER*8
  address of the calling-standard defined "argument block".

  The first element in the array contains the argument count;
  subsequent elements contain the INTEGER(KIND=8) address of the
  actual arguments.

  Formal (dummy) arguments which can be omitted must be declared
  VOLATILE.

  The following example shows the IARGPTR intrinsic:

  C      Test IARGPTR intrinsic function.
         EXTERNAL TEST_ARGPTR
         INTEGER*4 X,Y,Z,FOO
         X = 10
         Y = 20
         Z = 100
         FOO = 4

         PRINT 80, %LOC(X), %LOC(Y), %LOC(Z), %LOC(FOO)
  80     FORMAT (' Argument addresses: ',4(1X, Z16))
         CALL TEST_ARGPTR (4, X, Y, Z, FOO)
         END

         OPTIONS /EXTEND_SOURCE
         SUBROUTINE TEST_ARGPTR (N_ARGS)
         POINTER (II, I_ARGN)
         INTEGER*8 I_ARGN
         POINTER (I_PTR, I_VAL)
         INTEGER I_VAL

         II = IARGPTR()             ! Get address of arg block
         II = II + SIZEOF (II)      ! Get address of address of first arg

         DO I = 1, N_ARGS+1
          I_PTR = I_ARGN            ! Get address of actual from homed
                                    !   arg list
          print 90, I, I_PTR, I_VAL
  90      format ( ' Argument ',I2, ' address = ',Z16, ', contents = ',Z16)
          II = II + SIZEOF (II)  ! Get address of address of next arg
         END DO
         RETURN
         END

66  –  IBCHNG

  IBCHNG (integer, position)

  Class:  Elemental function - Generic

  Returns the reverse of the value of a specified bit in an integer.
  The low-order bit is position 0.

  Examples:

  Consider the following:

    INTEGER J, K
    J = IBCHNG(10, 2)         ! returns 14 = 1110
    K = IBCHNG(10, 1)         ! returns  8 = 1000

67  –  IBCLR

  IBCLR (integer, position)

  Class:  Elemental function - Generic

  Returns the value of the first argument with the specified bit set
  to 0 (bit clear).  The low-order bit is position 0.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  IBCLR  |   --     | INTEGER*1  | INTEGER*1   |
  |      |         | IIBCLR   | INTEGER*2  | INTEGER*4   |
  |      |         | JIBCLR   | INTEGER*4  | INTEGER*4   |
  |      |         | KIBCLR   | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

68  –  IBITS

  IBITS (integer, start-position, length)

  Class:  Elemental function - Generic

  Returns the value of the bits of the first argument specified by
  start-position and number of bits.  The low-order bit is position
  0.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  3   |  IBITS  |   --     | INTEGER*1  | INTEGER*1   |
  |      |         | IIBITS   | INTEGER*2  | INTEGER*2   |
  |      |         | JIBITS   | INTEGER*4  | INTEGER*4   |
  |      |         | KIBITS   | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

69  –  IBSET

  IBSET (integer, position)

  Class:  Elemental function - Generic

  Returns the value of the first argument with the specified bit set
  to 1 (bit set).  The low-order bit is position 0.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  IBSET  |   --     | INTEGER*1  | INTEGER*1   |
  |      |         | IIBSET   | INTEGER*2  | INTEGER*2   |
  |      |         | JIBSET   | INTEGER*4  | INTEGER*4   |
  |      |         | KIBSET   | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

70  –  ICHAR

  ICHAR (character)

  Class:  Elemental function - Generic

  Returns the position of a character in the processor's character
  set.

  The argument must have a length of 1.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |   --    |  --      | CHARACTER  | INTEGER*2   |
  |      |         | ICHAR    | CHARACTER  | INTEGER*4   |
  |      |         |  --      | CHARACTER  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

  This function cannot be passed as an actual argument.

71  –  IDATE

  IDATE (month, day, year)

  Class:  Subroutine

  Returns three integer values representing the current date.  The
  month is represented as the number of the month (1 - 12).  The day
  is represented as the day of the month.  The year is represented as
  the last two digits of the year.

72  –  IDIM

  See the DIM function.

73  –  IDINT

  See the INT function.

74  –  IDNINT

  See the NINT function

75  –  IEOR

  IEOR (integer, integer)

  Class:  Elemental function - Generic

  Performs an exclusive OR of the arguments on a bit by bit basis
  (bit exclusive OR).  This function can also be specified as XOR.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   | IEOR    |   --     | INTEGER*1  | INTEGER*1   |
  |      |         | IIEOR    | INTEGER*2  | INTEGER*2   |
  |      |         | JIEOR    | INTEGER*4  | INTEGER*4   |
  |      |         | KIEOR    | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

76  –  IFIX

  See the INT function.

77  –  ILEN

  ILEN (integer)

  Class:  Elemental function - Generic

  Returns the length (in bits) of the two's complement representation
  of an integer.

  The result type is the same as the argument.

  Examples:

  ILEN (4) has the value 3.

  ILEN (-4) has the value 2.

78  –  IMAG

  See the AIMAG intrinsic function.

79  –  INDEX

  INDEX (string, substring [,back] [,kind])

  Class:  Elemental function - Generic

  Returns the starting position of the substring as an INTEGER*4 or
  INTEGER*8 value.

  "string" and "substring" are of type character, "back" is of type
  logical, and "kind" is a scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "back" is absent or false, the leftmost substring is found. If
  "back" is true, the rightmost substring is found.

  Examples:

  INDEX ('FORTRAN', 'O', BACK = .TRUE.) has the value 2.

  INDEX ('XXXX', " ", BACK = .TRUE.) has the value 0.

  INDEX ('XXXX', "", BACK = .TRUE.) has the value 5.

80  –  INT

  INT (number [,kind])

  Class:  Elemental function - Generic

  Returns the largest integer whose absolute value does not exceed
  the absolute value of the argument and has the same sign as the
  argument.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that shown in the following table.
  If the processor cannot represent the result value in the kind of
  the result, the result is undefined.
  +------+-----------+----------+------------+-------------+
  | Args | Generic   | Specific |  Argument  | Result Type |
  +------+-----------+----------+------------+-------------+
  |  1   |  INT      |  --      | INTEGER*1  | INTEGER*2   |
  |      |           |  --      | INTEGER*1  | INTEGER*4   |
  |      |           |  --      | INTEGER*1  | INTEGER*8   |
  |      |           |  --      | INTEGER*2  | INTEGER*4   |
  |      |           |  --      | INTEGER*2  | INTEGER*8   |
  |      |           |  --      | INTEGER*4  | INTEGER*4   |
  |      |           |  --      | INTEGER*4  | INTEGER*8   |
  |      |           |  --      | INTEGER*8  | INTEGER*8   |
  |      |see note1  | IIFIX    | REAL*4     | INTEGER*2   |
  |      |           | IINT     | REAL*4     | INTEGER*2   |
  |      |see note2  | IFIX     | REAL*4     | INTEGER*4   |
  |      |           | JFIX     | INTEGER*1  | INTEGER*4   |
  |      |           |          | INTEGER*2  | INTEGER*4   |
  |      |           |          | INTEGER*4  | INTEGER*4   |
  |      |           |          | INTEGER*8  | INTEGER*4   |
  |      |           |          | REAL*4     | INTEGER*4   |
  |      |           |          | REAL*8     | INTEGER*4   |
  |      |           |          | REAL*16    | INTEGER*4   |
  |      |           |          | COMPLEX*8  | INTEGER*4   |
  |      |           |          | COMPLEX*16 | INTEGER*4   |
  |      |           |          | COMPLEX*32 | INTEGER*4   |
  |      |see note3  | INT      | REAL*4     | INTEGER*4   |
  |      |           | KIFIX    | REAL*4     | INTEGER*8   |
  |      |           | KINT     | REAL*4     | INTEGER*8   |
  |      |           | IIDINT   | REAL*8     | INTEGER*2   |
  |      |see note4  | IDINT    | REAL*8     | INTEGER*4   |
  |      |           | KIDINT   | REAL*4     | INTEGER*8   |
  |      |           | IIQINT   | REAL*16    | INTEGER*2   |
  |      |see note5  | IQINT    | REAL*16    | INTEGER*4   |
  |      |           | KIQINT   | REAL*16    | INTEGER*8   |
  |      |           |  --      | COMPLEX*8  | INTEGER*2   |
  |      |           |  --      | COMPLEX*8  | INTEGER*4   |
  |      |           |  --      | COMPLEX*8  | INTEGER*8   |
  |      |           |  --      | COMPLEX*16 | INTEGER*2   |
  |      |           |  --      | COMPLEX*16 | INTEGER*4   |
  |      |           |  --      | COMPLEX*16 | INTEGER*8   |
  |      |           |  --      | COMPLEX*32 | INTEGER*2   |
  |      |           |  --      | COMPLEX*32 | INTEGER*4   |
  |      |           |  --      | COMPLEX*32 | INTEGER*8   |
  |      |           | INT1     | INTEGER*1  | INTEGER*1   |
  |      |           |          | INTEGER*2  | INTEGER*1   |
  |      |           |          | INTEGER*4  | INTEGER*1   |
  |      |           |          | INTEGER*8  | INTEGER*1   |
  |      |           |          | REAL*4     | INTEGER*1   |
  |      |           |          | REAL*8     | INTEGER*1   |
  |      |           |          | REAL*16    | INTEGER*1   |
  |      |           |          | COMPLEX*8  | INTEGER*1   |
  |      |           |          | COMPLEX*16 | INTEGER*1   |
  |      |           |          | COMPLEX*32 | INTEGER*1   |
  |      |           | INT2     | INTEGER*1  | INTEGER*2   |
  |      |           |          | INTEGER*2  | INTEGER*2   |
  |      |           |          | INTEGER*4  | INTEGER*2   |
  |      |           |          | INTEGER*8  | INTEGER*2   |
  |      |           |          | REAL*4     | INTEGER*2   |
  |      |           |          | REAL*8     | INTEGER*2   |
  |      |           |          | REAL*16    | INTEGER*2   |
  |      |           |          | COMPLEX*8  | INTEGER*2   |
  |      |           |          | COMPLEX*16 | INTEGER*2   |
  |      |           |          | COMPLEX*32 | INTEGER*2   |
  |      |           | INT4     | INTEGER*1  | INTEGER*4   |
  |      |           |          | INTEGER*2  | INTEGER*4   |
  |      |           |          | INTEGER*4  | INTEGER*4   |
  |      |           |          | INTEGER*8  | INTEGER*4   |
  |      |           |          | REAL*4     | INTEGER*4   |
  |      |           |          | REAL*8     | INTEGER*4   |
  |      |           |          | REAL*16    | INTEGER*4   |
  |      |           |          | COMPLEX*8  | INTEGER*4   |
  |      |           |          | COMPLEX*16 | INTEGER*4   |
  |      |           |          | COMPLEX*32 | INTEGER*4   |
  |      |           | INT8     | INTEGER*1  | INTEGER*8   |
  |      |           |          | INTEGER*2  | INTEGER*8   |
  |      |           |          | INTEGER*4  | INTEGER*8   |
  |      |           |          | INTEGER*8  | INTEGER*8   |
  |      |           |          | REAL*4     | INTEGER*8   |
  |      |           |          | REAL*8     | INTEGER*8   |
  |      |           |          | REAL*16    | INTEGER*8   |
  |      |           |          | COMPLEX*8  | INTEGER*8   |
  |      |           |          | COMPLEX*16 | INTEGER*8   |
  |      |           |          | COMPLEX*32 | INTEGER*8   |
  +------+-----------+----------+------------+-------------+

  Note1: This function can also be specified as HFIX.
  Note2: For compatibility with older versions of
         Fortran, IFIX can also be specified as a generic
         function.
  Note3: Or JINT.
  Note4: Or JIDINT.  For compatibility with older versions of
         Fortran, IDINT can also be specified as a generic
         function.
  Note5: Or JIQINT.  For compatibility with older versions of
         Fortran, IQINT can also be specified as a generic
         function.

  These functions cannot be passed as actual arguments.

  The setting of compiler options specifying integer size can affect
  INT, IDINT, and IQINT.

  The setting of compiler options specifying integer size and real
  size can affect IFIX.

81  –  INT_PTR_KIND

  INT_PTR_KIND()

  Class:  Inquiry function - Specific

  Returns the INTEGER KIND that will hold an address.  This is a
  specific function that has no generic function associated with it.
  It must not be passed as an actual argument.

  The result is of type default integer.  The result is a scalar with
  the value equal to the value of the kind parameter of the integer
  data type that can represent an address on the host platform.

  The value is 8.

  The following example shows the INT_PTR_KIND intrinsic:

     REAL A(100)
     POINTER (P, A)
     INTEGER (KIND=INT_PTR_KIND()) SAVE_P
     P = MALLOC (400)
     SAVE_P = P

82  –  IOR

  IOR (integer, integer)

  Class:  Elemental function - Generic

  Performs a logical OR of the arguments on a bit by bit basis
  (bitwise inclusive OR).  This function can also be specified as OR.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  IOR    |  --      | INTEGER*1  | INTEGER*1   |
  |      |         | IIOR     | INTEGER*2  | INTEGER*2   |
  |      |         | JIOR     | INTEGER*4  | INTEGER*4   |
  |      |         | KIOR     | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

83  –  IQINT

  See the INT function.

84  –  IQNINT

  See the NINT function.

85  –  ISHA

  ISHA (integer, shift)

  Class:  Elemental function - Generic

  Arithmetically shifts an integer left or right by a specified
  number of bits.

  The "shift" is of type integer; it is the direction and distance of
  shift.

  The result type is the same as "integer".

  If "shift" is positive, the shift is to the left; if "shift" is
  negative, the shift is to the right.  If "shift" is zero, no shift
  is performed.

  Bits shifted out from the left or from the right, as appropriate,
  are lost.  If the shift is to the left, zeros are shifted in on the
  right.  If the shift is to the right, copies of the sign bit (0 for
  non-negative "integer"; 1 for negative "integer") are shifted in on
  the left.

  The kind of integer is important in arithmetic shifting because
  sign varies among integer representations (see the following
  example).  If you want to shift a one-byte or two-byte argument,
  you must declare it as INTEGER(1) or INTEGER(2).

  Examples:

  Consider the following:

    INTEGER(1) i, res1
    INTEGER(2) j, res2
    i = -128             ! equal to  10000000
    j = -32768           ! equal to  10000000 00000000
    res1  = ISHA (i, -4) ! returns 11111000 = -8
    res2  = ISHA (j, -4) ! returns 11111000 00000000 = -2048

86  –  ISHC

  ISHC (integer, shift)

  Class:  Elemental function - Generic

  Rotates an integer left or right by specified number of bits.  Bits
  shifted out one end are shifted in the other end.  No bits are
  lost.

  The "shift" is of type integer; it is the direction and distance of
  rotation.

  If "shift" is positive, "integer" is rotated left "shift" bits.  If
  "shift" is negative, "integer" is rotated right "shift" bits.  Bits
  shifted out one end are shifted in the other.  No bits are lost.

  The kind of integer is important in circular shifting.  With an
  INTEGER(4) argument, all 32 bits are shifted.  If you want to
  rotate a one-byte or two-byte argument, you must declare it as
  INTEGER(1) or INTEGER(2).

  Examples:

  Consider the following:

    INTEGER(1) i, res1
    INTEGER(2) j, res2
    i = 10                 ! equal to  00001010
    j = 10                 ! equal to  00000000 00001010
    res1  = ISHC (i, -3)   ! returns 01000001 =  65
    res2  = ISHC (j, -3)   ! returns 01000000 00000001 = 16385

87  –  ISHFT

  ISHFT (integer, shift)

  Class:  Elemental function - Generic

  Performs a bitwise logical shift - the "shift" is the
  no-of-positions.

  The integer is shifted left (if "shift" is positive) or right (if
  "shift" is negative) by ABS(shift) bits.  If ABS(shift) is greater
  than or equal to the length in bits of the integer argument, the
  result is zero.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  ISHFT  |   --     | INTEGER*1  | INTEGER*1   |
  |      |         | IISHFT   | INTEGER*2  | INTEGER*2   |
  |      |         | JISHFT   | INTEGER*4  | INTEGER*4   |
  |      |         | KISHFT   | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+
  Bits shifted out are lost.  Zeros are shifted in from the opposite
  end.

88  –  ISHFTC

  ISHFTC (integer, shift [,size])

  Class:  Elemental function - Generic

  Performs a bitwise circular shift - "shift" is the no-of-positions
  and "size" is the no-of-bits.

  The rightmost "size" bits of the integer argument are circularly
  shifted by "shift" places; bits in the integer argument beyond the
  value specified by "size" are unaffected.

  If "shift is positive, the shift is to the left; if negative, the
  shift is to the right.  If "size" is omitted, it is assumed to have
  the value BIT_SIZE (integer).
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  3   | ISHFTC  | IISHFTC  | INTEGER*2  | INTEGER*4   |
  |      |         | JISHFTC  | INTEGER*4  | INTEGER*4   |
  |      |         | KISHFTC  | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

89  –  ISHL

  ISHL (integer, shift)

  Class:  Elemental function - Generic

  Logically shifts an integer left or right by the specified bits.
  Zeros are shifted in from the opposite end.

  The "shift" is of type integer; it is the direction and distance of
  shift.

  Unlike circular or arithmetic shifts, which can shift ones into the
  number being shifted, logical shifts shift in zeros only,
  regardless of the direction or size of the shift.  The integer
  kind, however, still determines the end that bits are shifted out
  of, which can make a difference in the result (see the following
  example).

  Examples:

  Consider the following:

    INTEGER(1) i, res1
    INTEGER(2) j, res2
    i = 10                ! equal to  00001010
    j = 10                ! equal to  00000000 00001010
    res1  = ISHL (i, 5)   ! returns 01000000 = 64
    res2  = ISHL (j, 5)   ! returns 00000001 01000000 = 320

90  –  ISIGN

  See the SIGN function.

91  –  ISNAN

  ISNAN (real-number)

  Class:  Elemental function - Generic

  Tests whether IEEE REAL*4 (S_floating) and REAL*8 (T_floating)
  numbers are Not-a-Number (NaN) values.  To use this function,
  compiler option /FLOAT=IEEE_FLOAT must be set.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  ISNAN  |   --     | REAL*4     | LOGICAL*4   |
  |      |         |          | REAL*8     | LOGICAL*4   |
  +------+---------+----------+------------+-------------+

92  –  KIND

  KIND (number)

  Class:  Inquiry function - Generic

  Returns the value of the kind type parameter of the argument.  For
  more information on kind type parameters, see the
  reference manual.

  The argument can be of any intrinsic type.  The result is a scalar
  of type default integer.

  Examples:

  KIND (0.0) has the kind type value of default real type.

  KIND (12) has the kind type value of default integer type.

93  –  LBOUND

  LBOUND (array, [,dim] [,kind])

  Class:  Inquiry function - Generic

  Returns the lower bounds for all dimensions of an array, or the
  lower bound for a specified dimension.

  The "array" cannot be an allocatable array that is not allocated,
  or a disassociated pointer.  The "dim" is a scalar integer with a
  value in the range 1 to n, where "n" is the rank of "array".  The
  "kind" must be a scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "dim" is present, the result is a scalar.  Otherwise, the result
  is a rank-one array with one element for each dimension of "array".
  Each element in the result corresponds to a dimension of "array".

  If "array" is an array section or an array expression that is not a
  whole array or array structure component, each element of the
  result has the value 1.

  The setting of compiler options that specify integer size can
  affect the result of this function.

  Examples

  Consider the following:

  REAL ARRAY_A (1:3, 5:8)
  REAL ARRAY_B (2:8, -3:20)

  LBOUND (ARRAY_A) is (1, 5).  LBOUND (ARRAY_A, DIM=2) is 5.

  LBOUND (ARRAY_B) is (2, -3).  LBOUND (ARRAY_B (5:8, :)) is (1,1)
  because the arguments are array sections.

94  –  LEADZ

  LEADZ (integer)

  Class:  Elemental function - Generic

  Returns the number of leading zeros in the binary representation of
  the integer argument.  The result type is the same as the argument.

  Example:

  Consider the following:

    INTEGER*8 J, TWO
    PARAMETER (TWO=2)
    DO J= -1, 40
      TYPE *, LEADZ(TWO**J)  ! Prints 64 down to 23 (leading zeros)
    ENDDO
    END

95  –  LEN

  LEN (string [,kind])

  Class:  Inquiry function - Generic

  Returns the number of characters in the argument.  The argument
  must be a character expression.

  The "kind" must be a scalar integer initialization expression.

  The result is an INTEGER*4 or INTEGER*8 value.  If "kind" is
  present, the kind parameter of the result is that specified by
  "kind"; otherwise, the kind parameter of the result is that of
  default integer.  If the processor cannot represent the result
  value in the kind of the result, the result is undefined.

  The setting of compiler options that specify integer size can
  affect the result of this function.

96  –  LEN_TRIM

  LEN_TRIM (string [,kind])

  Class:  Elemental function - Generic

  Returns the length of the character argument without counting
  trailing blank characters.

  The "string" must be of type character.  The "kind" must be a
  scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  Examples:

  LEN_TRIM ('   C  D   ') has the value 7.

  LEN_TRIM ('   ') has the value 0.

97  –  LGE

  LGE (string-a, string-b)

  Class:  Elemental function - Generic

  Returns a value of true if the first character string is lexically
  greater than or equal to the second character string, based on the
  ASCII collating sequence - even if the processor's default
  collating sequence is different.  In VSI Fortran, LGE is
  equivalent to the >= operator.

  The ASCII collating sequence determines the relationship between
  the arguments.

  The arguments must be character expressions.  The result is a
  LOGICAL*4 value.

  This function cannot be passed as an actual argument.

98  –  LGT

  LGT (string-a, string-b)

  Class:  Elemental function - Generic

  Returns a value of true if the first character string is greater
  than the second character string, based on the ASCII collating
  sequence - even if the processor's default collating sequence is
  different.  In VSI Fortran, LGT is equivalent to the > operator.

  The ASCII collating sequence determines the relationship between
  the arguments.

  The arguments must be character expressions.  The result is a
  LOGICAL*4 value.

  This function cannot be passed as an actual argument.

99  –  LLE

  LLE (string-a, string-b)

  Class:  Elemental function - Generic

  Returns a value of true if the first character string is less than
  or equal to the second character string, based on the ASCII
  collating sequence - even if the processor's default collating
  sequence is different.  In VSI Fortran, LLE is equivalent to the
  <= operator.

  The ASCII collating sequence determines the relationship between
  the arguments.

  The arguments must be character expressions.  The result is a
  LOGICAL*4 value.

  This function cannot be passed as an actual argument.

100  –  LLT

  LLT (string-a, string-b)

  Class:  Elemental function - Generic

  Returns a value of true if the first character string is less than
  the second character string, based on the ASCII collating sequence
  - even if the processor's default collating sequence is different.
  In VSI Fortran, LLT is equivalent to the < operator.

  The ASCII collating sequence determines the relationship between
  the arguments.

  The arguments must be character expressions.  The result is a
  LOGICAL*4 value.

  This function cannot be passed as an actual argument.

101  –  LOC

  LOC (arg)

  Class:  Inquiry function - Generic

  Returns the internal address of a storage item.

  The argument can be a variable, an array or record field reference,
  a procedure, or a constant; it can be of any data type.  It must
  not be the name of an internal procedure or statement function.  If
  it is a pointer, it must be defined and associated with a target.

  The result is of type INTEGER*8.  The value of the result
  represents the address of the data object or, in the case of
  pointers, the address of its associated target.  If the argument is
  not valid, the result is undefined.

  On Open VMS systems, in the case of global symbolic constants, LOC
  returns the value of the constant rather than an address.

  The LOC intrinsic serves the same purpose as the %LOC built-in
  function.

  This function cannot be passed as an actual argument.

102  –  LOG

  LOG (number)

  Class:  Elemental function - Generic

  Returns the natural log (base e) of a real or complex argument.

  If the argument is real, its value must be greater than zero.  If
  the argument is complex, its value must not be (0.,0.).
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  LOG    | ALOG     | REAL*4     | REAL*4      |
  |      |         | DLOG     | REAL*8     | REAL*8      |
  |      |         | QLOG     | REAL*16    | REAL*16     |
  |      |         | CLOG     | COMPLEX*8  | COMPLEX*8   |
  |      |         | CDLOG    | COMPLEX*16 | COMPLEX*16  |
  |      |         | ZLOG     | COMPLEX*16 | COMPLEX*16  |
  |      |         | CQLOG    | COMPLEX*32 | COMPLEX*32  |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect ALOG and CLOG.

103  –  LOG10

  LOG10 (real-number)

  Class:  Elemental function - Generic

  Returns the common log (base 10) of the argument.  The argument
  must be greater than zero.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  LOG10  | ALOG10   | REAL*4     | REAL*4      |
  |      |         | DLOG10   | REAL*8     | REAL*8      |
  |      |         | QLOG10   | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect ALOG10.

104  –  LOGICAL

  LOGICAL (logical-exp, [,kind])

  Class:  Elemental function - Generic

  Converts the logical value of the argument to a logical of
  different kind type parameters.

  The setting of integer size compiler options can affect this
  function.

  Examples:

  LOGICAL (L .OR.  .NOT.  L) has the value true and is of type
  default logical regardless of the kind type parameter of logical
  variable L.

  LOGICAL (.FALSE., 2) has the value false, with the kind type
  parameter of INTEGER(KIND=2).

105  –  MALLOC

  MALLOC (integer)

  Class:  Elemental function - Specific

  Allocates a block of memory.

  The argument must be of type integer.  This value is the size in
  bytes of memory to be allocated.  If the argument is INTEGER*8, a
  64-bit (P3) space is allocated.

  The result is of type INTEGER*8.  The result is the starting
  address of the allocated memory.  The memory allocated can be freed
  by using the FREE intrinsic function.

  This function cannot be passed as an actual argument.

  Examples:

  Consider the following:

  INTEGER(4) SIZE
  REAL(4) STORAGE(*)
  POINTER (ADDR, STORAGE)     ! ADDR will point to STORAGE
  SIZE = 1024                 ! Size in bytes
  ADDR = MALLOC(SIZE)         ! Allocate the memory
  CALL FREE(ADDR)             ! Free it
  END

106  –  MATMUL

  MATMUL (matrix-a, matrix-b)

  Class:  Transformational function - Generic

  Performs matrix multiplication of numeric or logical matrices.

  The "matrix"s can be arrays of rank one or two.  At least one
  argument must be rank two.  The size of the first (or only)
  dimension of "matrix-b" must equal the last (or only) dimension of
  "matrix-a".

  The type of the resulting array depends on the data types of the
  arguments.  The rank and shape of the result follows:

   o  If "matrix-a" has shape (n,m) and "matrix-b" has shape (m,k),
      the result is a rank-two array with shape (n,k).

   o  If "matrix-a" has shape (m) and "matrix-b" has shape (m,k), the
      result is a rank-one array with shape (k).

   o  If "matrix-a" has shape (n,m) and "matrix-b" has shape (m), the
      result is a rank-one array with shape (n).

  Examples:

  Consider the following:

  A is the matrix |2 3 4|, B is the matrix |2 3|,
                  |3 4 5|                  |3 4|
                                           |4 5|

  X is vector (1, 2), and Y is vector (1, 2, 3).

  The result of MATMUL (A, B) is the matrix-matrix product AB with
  the value

    |29 38|
    |38 50|

  The result of MATMUL (X, A) is the vector-matrix product XA with
  the value (8, 11, 14).

  The result of MATMUL (A, Y) is the matrix-vector product AY with
  the value (20, 26).

107  –  MAX

  MAX (number, number [, ...])

  Class:  Elemental function - Generic

  Returns the greatest of the values specified in the argument list.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  n   |  MAX    |   --     | INTEGER*1  | INTEGER*1   |
  |      |         |   --     | INTEGER*1  | REAL*4      |
  |      |         | IMAX0    | INTEGER*2  | INTEGER*2   |
  |      |         | AIMAX0   | INTEGER*2  | REAL*4      |
  |      |see note1| MAX0     | INTEGER*4  | INTEGER*4   |
  |      |see note2| AMAX0    | INTEGER*4  | REAL*4      |
  |      |         | KMAX0    | INTEGER*8  | INTEGER*8   |
  |      |         | AKMAX0   | INTEGER*8  | REAL*4      |
  |      |         | IMAX1    | REAL*4     | INTEGER*2   |
  |      |see note3| MAX1     | REAL*4     | INTEGER*4   |
  |      |         | KMAX1    | REAL*4     | INTEGER*8   |
  |      |         | AMAX1    | REAL*4     | REAL*4      |
  |      |         | DMAX1    | REAL*8     | REAL*8      |
  |      |         | QMAX1    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

  Note1: Or JMAX0.
  Note2: Or AJMAX0.  AMAX0 is the same as REAL(MAX). For
         compatibility with older versions of Fortran, AMAX0
         can also be specified as a generic function.
  Note3: Or JMAX1.  MAX1 is the same as INT(MAX). For
         compatibility with older versions of Fortran, MAX1
         can also be specified as a generic function.

  These functions cannot be passed as actual arguments.

  The setting of compiler options specifying integer size can affect
  MAX1.

  The setting of compiler options specifying real size can affect
  AMAX1.

108  –  MAX0

  See the MAX function.

109  –  MAX1

  See the MAX function.

110  –  MAXEXPONENT

  MAXEXPONENT (real-arg)

  Class:  Inquiry function - Generic

  Returns the maximum exponent in the model representing the same
  type and kind type parameter as the argument.  The argument can be
  scalar or array valued.

  The model for real numbers is described in the HP Fortran for
  OpenVMS Language Reference Manual.

  Example:

  If X is REAL*4 type, MAXEXPONENT (X) has the value 128.

111  –  MAXLOC

  MAXLOC (array [,dim] [,mask] [,kind])

  Class:  Transformational function - Generic

  Returns the location of the maximum value of all elements in an
  array, a set of elements in an array, or elements in a specified
  dimension of an array.

  The "array" can be of type integer or real.  The "dim" must be a
  scalar integer with a value in the range 1 to n, where "n" is the
  rank of "array".  The "mask" must be a logical array conformable
  with "array".  The "kind" must be a scalar integer initialization
  expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "dim" is absent, the result is an array with rank that is one
  less than "array", and shape (d1, d2,..., d"dim"-1, d"dim"+1,...,
  dn), where (d1, d2,..., dn) is the shape of "array".

  If "kind" is present, the kind parameter of the result is that
  specified by "kind"; otherwise, the kind parameter of the result is
  that of default integer.  If the processor cannot represent the
  result value in the kind of the result, the result is undefined.

  The result of MAXLOC (array) is a rank-one array whose elements
  form the subscript of the location of the element with the maximum
  value in "array".

  The result of MAXLOC (array, mask=mask) is a rank-one array whose
  elements form the subscript of the location of the element with the
  maximum value corresponding to the condition specified by "mask".

  If more than one element has maximum value, the element whose
  subscripts are returned is the first such element, taken in array
  element order.  If "array" has size zero, or every element of
  "mask" has the value .FALSE., the value of the result is undefined.

  Examples:

  The value of MAXLOC ((/3, 7, 4, 7/)) is 2.

  Consider that A is the array

   | 4  0 -3  2|
   | 3  1 -2  6|
   |-1 -4  5 -5|

  MAXLOC (A, MASK=A .LT.  5) has the value (1, 1).  This is true even
  if A has a declared bound other than 1.

  MAXLOC (A, DIM=1) has the value (1, 2, 3, 2).

  MAXLOC (A, DIM=2) has the value (1, 4, 3).

112  –  MAXVAL

  MAXVAL (array [,dim] [,mask]

  Class:  Transformational function - Generic

  Returns the maximum value of all elements in an array, a set of
  elements in an array, or elements in a specified dimension of an
  array.

  The array can be of type integer or real.  The "dim" must be a
  scalar integer with a value in the range 1 to n, where "n" is the
  rank of "array".  The "mask" must be a logical array conformable
  with "array".

  The result is the same data type as "array".  The result is a
  logical array with the same kind type parameter as "array".  The
  result is a scalar if "dim" is absent or "array" has rank one.
  Otherwise, the result is an array with rank that is one less than
  "array", and shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn), where
  (d1, d2,..., dn) is the shape of "array".

  The result of MAXVAL (array) has a value equal to the maximum value
  of all the elements in "array".

  The result of MAXVAL (array, mask=mask) has a value equal to the
  maximum value of the elements in "array" corresponding to the
  condition specified by "mask".

  If "array" has size zero or if there are no true elements in
  "mask," the result has the value of the negative number of the
  largest magnitude supported by the processor for numbers of the
  type and kind type parameter of "array".

  Examples:

  The value of MAXVAL ((/2, 3, 4/)) is 4.

  The value of MAXVAL (B, MASK=B .LT.  0.0) finds the maximum of the
  negative elements of B.

  Consider that C is the array

   |2 3 4|
   |5 6 7|

  MAXVAL (C, DIM=1) has the value (5, 6, 7).

  MAXVAL (C, DIM=2) has the value (4, 7).

113  –  MERGE

  MERGE (tsource, fsource, mask)

  Class:  Elemental function - Generic

  Selects between two values or between corresponding elements in two
  arrays, according to the condition specified by a logical mask.

  The "tsource" and "fsource" can be scalars or arrays; they must
  have the same type and type parameters.  The "mask" is a logical
  array.

  The result type is the same as "tsource".  The value of "mask"
  determines whether the result value is taken from "tsource" (if
  "mask" is true) or "fsource" (if "mask" is false).

  Examples:

  For MERGE (1.0, 0.0, R < 0), if R is -3 the merge has the value
  1.0, while if R is 7 the merge has the value 0.0.

  Consider that TSOURCE is the array |1 3 5|, FSOURCE is the
                                     |2 4 6|

  array |8 9 0|, and MASK is the array |F T T|.
        |1 2 3|                        |T T F|

  MERGE (TSOURCE, FSOURCE, MASK) produces the result: |8 3 5|.
                                                      |2 4 3|

114  –  MIN

  MIN (number, number [, ...])

  Class:  Elemental function - Generic

  Returns the lowest of the values specified in the argument list.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  n   |  MIN    |   --     | INTEGER*1  | INTEGER*1   |
  |      |         |   --     | INTEGER*1  | REAL*4      |
  |      |         | IMIN0    | INTEGER*2  | INTEGER*2   |
  |      |         | AIMIN0   | INTEGER*2  | REAL*4      |
  |      |see note1| MIN0     | INTEGER*4  | INTEGER*4   |
  |      |see note2| AMIN0    | INTEGER*4  | REAL*4      |
  |      |         | KMIN0    | INTEGER*8  | INTEGER*8   |
  |      |         | AKMIN0   | INTEGER*8  | REAL*4      |
  |      |         | IMIN1    | REAL*4     | INTEGER*2   |
  |      |see note3| MIN1     | REAL*4     | INTEGER*4   |
  |      |         | KMIN1    | REAL*4     | INTEGER*8   |
  |      |         | AMIN1    | REAL*4     | REAL*4      |
  |      |         | DMIN1    | REAL*8     | REAL*8      |
  |      |         | QMIN1    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

  Note1: Or JMIN0.
  Note2: Or AJMIN0.  AMIN0 is the same as REAL(MIN). For
         compatibility with older versions of Fortran, AMIN0
         can also be specified as a generic function.
  Note3: Or JMIN1.  MIN1 is the same as INT(MIN). For
         compatibility with older versions of Fortran, MIN1
         can also be specified as a generic function.

  These functions cannot be passed as actual arguments.

  The setting of compiler options specifying integer size can affect
  MIN1.

  The setting of compiler options specifying real size can affect
  AMIN1.

115  –  MIN0

  See the MIN function.

116  –  MIN1

  See the MIN function.

117  –  MINEXPONENT

  MINEXPONENT (real-arg)

  Class:  Inquiry function - Generic

  Returns the minimum exponent in the model representing the same
  type and kind type parameter as the argument.  The argument can be
  scalar or array valued.

  The model for real numbers is described in the HP Fortran for
  OpenVMS Language Reference Manual.

  Example:

  If X is REAL*4 type, MINEXPONENT (X) has the value -125.

118  –  MINLOC

  MINLOC (array [,dim] [,mask] [,kind])

  Class:  Transformational function - Generic

  Returns the location of the minimum value of all elements in an
  array, a set of elements in an array, or elements in a specified
  dimension of an array.

  The "array" can be of type integer or real.  The "dim" must be a
  scalar integer with a value in the range 1 to n, where "n" is the
  rank of "array".  The "mask" must be a logical array conformable
  with "array".  The "kind" must be a scalar integer initialization
  expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "dim" is absent, the result is an array with rank that is one
  less than "array", and shape (d1, d2,..., d"dim"-1, d"dim"+1,...,
  dn), where (d1, d2,..., dn) is the shape of "array".

  If "kind" is present, the kind parameter of the result is that
  specified by "kind"; otherwise, the kind parameter of the result is
  that of default integer.  If the processor cannot represent the
  result value in the kind of the result, the result is undefined.

  The result of MINLOC (array) is a rank-one array whose elements
  form the subscript of the location of the element with the minimum
  value in "array".

  The result of MINLOC (array, mask=mask) is a rank-one array whose
  elements form the subscript of the location of the element with the
  minimum value corresponding to the condition specified by "mask".

  If more than one element has minimum value, the element whose
  subscripts are returned is the first such element, taken in array
  element order.  If "array" has size zero, or every element of
  "mask" has the value .FALSE., the value of the result is undefined.

  Examples:

  The value of MINLOC ((/3, 1, 4, 1/)) is 2.

  Consider that A is the array

   | 4  0 -3  2|
   | 3  1 -2  6|
   |-1 -4  5 -5|

  MINLOC (A, MASK=A .GT.  -5) has the value (3, 2).  This is true
  even if A has a declared bound other than 1.

  MAXLOC (A, DIM=1) has the value (3, 3, 1, 3).

  MAXLOC (A, DIM=2) has the value (3, 3, 4).

119  –  MINVAL

  MINVAL (array [,dim] [,mask]

  Class:  Transformational function - Generic

  Returns the minimum value of all elements in an array, a set of
  elements in an array, or elements in a specified dimension of an
  array.

  The array can be of type integer or real.  The "dim" must be a
  scalar integer with a value in the range 1 to n, where "n" is the
  rank of "array".  The "mask" must be a logical array conformable
  with "array".

  The result is the same data type as "array".  The result is a
  logical array with the same kind type parameter as "array".  The
  result is a scalar if "dim" is absent or "array" has rank one.
  Otherwise, the result is an array with rank that is one less than
  "array", and shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn), where
  (d1, d2,..., dn) is the shape of "array".

  The result of MINVAL (array) has a value equal to the minimum value
  of all the elements in "array".

  The result of MINVAL (array, mask=mask) has a value equal to the
  minimum value of the elements in "array" corresponding to the
  condition specified by "mask".

  If "array" has size zero or if there are no true elements in
  "mask," the result has the value of the positive number of the
  largest magnitude supported by the processor for numbers of the
  type and kind type parameter of "array".

  Examples:

  The value of MINVAL ((/2, 3, 4/)) is 2.

  The value of MINVAL (B, MASK=B .GT.  0.0) finds the minimum of the
  positive elements of B.

  Consider that C is the array

   |2 3 4|
   |5 6 7|

  MINVAL (C, DIM=1) has the value (2, 3, 4).

  MINVAL (C, DIM=2) has the value (2, 5).

120  –  MOD

  MOD (dividend, divisor)

  Class:  Elemental function - Generic

  Divides the first argument by the second and returns the remainder.
  +------+----------+----------+------------+-------------+
  | Args | Generic  | Specific |  Argument  | Result Type |
  +------+----------+----------+------------+-------------+
  |  2   |  MOD     |  --      | INTEGER*1  | INTEGER*1   |
  |      |          | IMOD     | INTEGER*2  | INTEGER*2   |
  |      |see note1 | MOD      | INTEGER*4  | INTEGER*4   |
  |      |          | KMOD     | INTEGER*8  | INTEGER*8   |
  |      |see note2 | AMOD     | REAL*4     | REAL*4      |
  |      |          | DMOD     | REAL*8     | REAL*8      |
  |      |          | QMOD     | REAL*16    | REAL*16     |
  +------+----------+----------+------------+-------------+

  Note1: Or JMOD.
  Note2: The setting of compiler options specifying real
         size can affect AMOD.

121  –  MODULO

  MODULO (number-a, number-b)

  Class:  Elemental function - Generic

  Returns the modulo of the arguments.  The arguments can be integer
  or real type.  They must both be the same type and kind type
  parameter.

  The result is the same type as the arguments.

  If "number-a" is of type integer and "number-b" is not equal to
  zero, the value of the result is "number-a" -
  FLOOR(REAL("number-a")/REAL("number-b")) * "number-b".  If
  "number-a" is of type real and "number-b" is not equal to zero, the
  value of the result is "number-a" - FLOOR("number-a"/"number-b").
  If "number-b" is equal to zero, the result is undefined.

  Examples:

  MODULO (7, 3) has the value 1.

  MODULO (9, -6) has the value -3.

  MODULO (-9, 6) has the value 3.

122  –  MULT_HIGH

  MULT_HIGH (integer*8, integer*8)

  Class:  Elemental function - Specific

  A function that multiplies two 64-bit unsigned integers.  The
  result is of type INTEGER*8.  The result value is the upper
  (leftmost) 64 bits of the 128-bit unsigned result.

  This function cannot be passed as an actual argument.

  Consider the following:

          INTEGER(8) I,J,K
          I=2_8**53
          J=2_8**51
          K = MULT_HIGH (I,J)
          PRINT *,I,J,K
          WRITE (6,1000)I,J,K
  1000    FORMAT (' ', 3(Z,1X))
          END

  This example prints the following:

    9007199254740992      2251799813685248         1099511627776
        20000000000000           8000000000000             10000000000

123  –  MY_PROCESSOR

  MY_PROCESSOR ()

  Class:  Inquiry function - Specific

  Returns the identifying number of the calling process.  This is a
  specific function that has no generic function associated with it.
  It must not be passed as an actual argument.

  The result is a scalar of type default integer.  The result value
  is the identifying number of the physical processor from which the
  call is made.

  The value is in the range 0 to "n"-1, where "n" is the value
  returned by NUMBER_OF_PROCESSORS.

124  –  MVBITS

  MVBITS (from, frompos, len, to, topos)

  Class:  Elemental subroutine

  Copies a sequence of bits (a bit field) from one location to
  another.  The following arguments can be of any integer data type:

     from     Represents the location from which a bit
              field is transferred.

     frompos  Identifies the first bit position in the
              field transferred from "from". It must not
              be negative. "frompos" + "len" must be less
              than or equal to BIT_SIZE (from).

     len      Identifies the length of the field transferred
              from "from".  It must not be negative.

     to       Represents the location to which a bit field
              is transferred. It must have the same kind
              parameter as "from".  "to" is set by copying
              the sequence of bits of length "len", starting
              at position "frompos" of "from" to position
              "topos" of "to".  No other bits of "to"
              are altered.

              On return, the "len" bits of "to" (starting
              at "topos") are equal to the value that "len"
              bits of "from" (starting at "frompos") had
              on entry.

     topos    Identifies the starting position (within "to")
              for the bits being transferred.  It must not
              be negative.  "topos" + "len" must be less than
              or equal to BIT_SIZE (to).)

  You can also specify the following specific subroutines:

    IMVBITS   All arguments must be INTEGER*2.
    JMVBITS   Arguments can be INTEGER*2 or INTEGER*4; at least
              one must be INTEGER*4.
    KMVBITS   Arguments can be INTEGER*2, INTEGER*4, or INTEGER*8;
              at least one must be INTEGER*8.

125  –  NEAREST

  NEAREST (real-number-a, real-number-b)

  Class:  Elemental function - Generic

  Returns the nearest different number (representable on the
  processor) in a given direction.

  The result type is the same as "real-number-a"; a positive
  "real-number-b" returns the nearest number in the direction of
  positive infinity. A negative one goes in the direction of
  negative infinity.

  Example:

  If 3.0 and 2.0 are REAL*4 values, NEAREST (3.0, 2.0) has the
  value 3 + 2**-22, which equals approximately 3.0000002, while
  NEAREST (3.0, -2.0) has the value 3-2**-22, which approximately
  equals 2.9999998.  For more information on the REAL*4 model,
  see the HP Fortran for OpenVMS Language Reference Manual.

126  –  NINT

  NINT (real-number [,kind])

  Class:  Elemental function - Generic

  Returns the value of the integer nearest to the value of the
  argument.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that shown in the following table.
  If the processor cannot represent the result value in the kind of
  the result, the result is undefined.
  +------+-----------+----------+------------+-------------+
  | Args | Generic   | Specific |  Argument  | Result Type |
  +------+-----------+----------+------------+-------------+
  |   1  |           | ININT    | REAL*4     | INTEGER*2   |
  |      |see note1  | NINT     | REAL*4     | INTEGER*4   |
  |      |           | KNINT    | REAL*4     | INTEGER*8   |
  |      |           | IIDNNT   | REAL*8     | INTEGER*2   |
  |      |see note2  | IDNINT   | REAL*8     | INTEGER*4   |
  |      |           | KIDNNT   | REAL*8     | INTEGER*8   |
  |      |           | IIQNNT   | REAL*16    | INTEGER*2   |
  |      |see note3  | IQNINT   | REAL*16    | INTEGER*4   |
  |      |           | KIQNNT   | REAL*16    | INTEGER*8   |
  +------+-----------+----------+------------+-------------+

  Note1: Or JNINT.
  Note2: Or JIDNNT.  For compatibility with older versions
         of Fortran, IDNINT can also be specified as a generic
         function.
  Note3: Or JIQNNT. For compatibility with older versions
         of Fortran,  IQNINT can also be specified as a generic
         function.

  The setting of compiler options specifying integer size can affect
  NINT, IDNINT, and IQNINT.

127  –  NOT

  NOT (integer)

  Class:  Elemental function - Generic

  Complements each bit of the argument (bitwise complement).
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  NOT    |  --      | INTEGER*1  | INTEGER*1   |
  |      |         | INOT     | INTEGER*2  | INTEGER*2   |
  |      |         | JNOT     | INTEGER*4  | INTEGER*4   |
  |      |         | KNOT     | INTEGER*8  | INTEGER*8   |
  +------+---------+----------+------------+-------------+

128  –  NULL

  NULL ([mold])

  Class:  Transformational function - Generic

  Initializes a pointer as disassociated when it is declared.

  Argument "mold" is optional and must be a pointer; it can be of any
  type.

  The status of the pointer can be associated, disassociated, or
  undefined.  If the pointer's status is associated, the target does
  not have to be defined with a value.

  The result type is the same as "mold", if present.  Otherwise, the
  type (and rank) is determined by the pointer that becomes
  associated with the result:

  If NULL () Appears...         Type is Determined From...
  ------------------------      -----------------------------------
  Right side of pointer         The pointer on the left side
    assignment

  Initialization for an         The object
    object in a declaration

  Default initialization        The component
    for a component

  In a structure constructor    The corresponding component

  As an actual argument         The corresponding dummy argument

  In a DATA statement           The corresponding pointer object

  It returns a disassociated pointer.

  Example:

    INTEGER, POINTER :: POINT1 => NULL()

  This statement defines the initial association status of POINT1 to
  be disassociated.

129  –  NUMBER_OF_PROCESSORS

  NUMBER_OF_PROCESSORS ([dim])

  Class:  Inquiry function - Specific

  Returns the total number of processors (peers) available to the
  program along an optional dimension of the processor array.

  The "dim" has no effect on single-processor workstations.

  The result is of type default integer.  On single-processor
  workstations, the result is always 1.

  This function cannot be passed as an actual argument.

130  –  NWORKERS

  NWORKERS ()

  Class:  Elemental function - Specific

  Returns an INTEGER*4 value that represents the total number of
  processes executing an application.  However, since VSI Fortran
  only does serial processing, NWORKERS always returns 1.

  NWORKERS is provided for compatibility with HP Fortran 77 for
  OpenVMS VAX systems.

  This function cannot be passed as an actual argument.

131  –  PACK

  PACK (array, mask [,vector])

  Class:  Transformational function - Generic

  Takes elements from an array and packs them into a rank-one array
  under the control of a mask.

  The "mask" must be of logical type and conformable with "array".
  The "vector" must be a rank-one array with the same type and type
  parameters as "array".  Its size must be at least t, where "t" is
  the number of true elements in "mask".  If "mask" is a scalar with
  value true, "vector" must have at least as many elements as there
  are in "array".

  Elements in "vector" are used to fill out the result array if there
  are not enough elements selected by "mask."

  The result is a rank-one array with the same type and type
  parameters as "array".  If "vector" is present, the size of the
  result is that of "vector".  Otherwise, the size of the result is
  the number of true elements in "mask", or the number of elements in
  "array" (if "mask" is a scalar with value true).

  Elements in "array" are processed in array element order to form
  the result array.  Element i of the result is the element of
  "array" that corresponds to the ith true element of "mask".

  If "vector" is present and has more elements than there are true
  values in "mask", any result elements that are empty (because they
  were not true according to "mask") are set to the corresponding
  values in "vector".

  Examples:

  Consider that N is the array |0 8 0|.
                               |0 0 0|
                               |7 0 0|

  PACK (N, MASK=N .NE.  0, VECTOR= (/1, 3, 5, 9, 11, 13/) produces
  the result (7, 8, 5, 9, 11, 13).

  PACK (N, MASK=N .NE.  0) produces the result (7, 8).

132  –  POPCNT

  POPCNT (integer)

  Class:  Elemental function - Generic

  A function that returns the number of 1 bits in the binary
  representation of the integer argument.  The result type is the
  same as the argument.

  Example:

  If the value of I is B'0...00011010110', the value of POPCNT(I) is
  5.

133  –  POPPAR

  POPPAR (integer*8)

  Class:  Elemental function - Generic

  A function that returns parity of an integer.  The result value is
  one if there are an odd number of 1 bits in the binary
  representation of the integer argument and zero if there are an
  even number.  The result type is the same as the argument.

  Example:

  If the value of I is B'0...00011010110', the value of POPPAR(I) is
  1.

134  –  PRECISION

  PRECISION (number)

  Class:  Inquiry function - Generic

  Returns the decimal precision in the model representing real
  numbers with the same kind type parameter as the argument.

  The "number" can be of real or complex type; it can be scalar or
  array valued.

  The result is a scalar of type default integer.  The result has the
  value INT((DIGITS("number") - 1) * LOG10(RADIX("number"))).  If
  RADIX("number") is an integral power of 10, 1 is added to the
  result.

  Example:

  If X is a REAL*4 value, PRECISION (X) has the value 6.  The value 6
  is derived from INT ((24-1) * LOG10 (2.)) = INT (6.92...).  For
  more information on the model for REAL*4, see the HP Fortran for
  OpenVMS Language Reference Manual.

135  –  PRESENT

  PRESENT (opt-argument)

  Class:  Inquiry function - Generic

  Returns whether or not an optional dummy argument is present (has
  an associated actual argument).

  Example:

  Consider the following:

  SUBROUTINE CHECK (X, Y)
    REAL X, Z
    REAL, OPTIONAL :: Y
    ...
    IF (PRESENT (Y)) THEN
      Z = Y
    ELSE
       Z = X * 2
    END IF
  END
  ...
  CALL CHECK (15.0, 12.0)      ! Causes B to be set to 12.0
  CALL CHECK (15.0)            ! Causes B to be set to 30.0

136  –  PROCESSORS_SHAPE

  PROCESSORS_SHAPE ()

  Class:  Inquiry function - Specific

  Returns the shape of an implementation-dependent hardware processor
  array.

  If used in a program compiled for a HP PSE cluster, the result
  is a rank-one array of type default integer containing the number
  of processors (peers) available to the program.  Otherwise, the
  result is always a rank-one array of size zero.

  This function cannot be passed as an actual argument.

137  –  PRODUCT

  PRODUCT (array, [,dim] [,mask])

  Class:  Transformational function - Generic

  Returns the product of all the elements in an entire array or in a
  specified dimension of an array.

  The "array" can be of integer or real type.  The "dim" is optional
  and must be a scalar integer with a value in the range 1 to n,
  where "n" is the rank of "array".  The "mask" is optional and must
  be a logical array that is conformable with "array".

  The result is the same data type as "array".  The result is a
  scalar if "dim" is absent or "array" has rank one.  Otherwise, the
  result is an array with rank that is one less than "array", and
  shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn), where (d1, d2,...,
  dn) is the shape of "array".

  If only "array" appears, the result is the product of all elements
  of "array".  If "array" has size zero, the result is 1.

  If "array" and "mask" both appear, the result is the product of all
  elements of "array" corresponding to true elements of "mask".  If
  "array" has size zero, or every element of "mask" has the value
  .FALSE., the result is 1.

  If "dim" also appears and "array" has rank one, the value is the
  same as PRODUCT (array [,mask=mask]).  Otherwise, the value of
  element (s1, s2,..., s"dim"-1, s"dim"+1,..., sn) of PRODUCT (array,
  dim, [,mask]) is equal to PRODUCT (array (s1, s2,..., s"dim"-1, :,
  s"dim"+1, ..., sn)) [mask=mask (s1, s2, ..., s"dim"-1, :, s "dim"+1
  ..., sn)].

  Examples:

  PRODUCT ((/2, 3, 4/)) and PRODUCT ((/2, 3, 4/), DIM=1) returns the
  value 24.

  PRODUCT (C, MASK=C .LT.  0.0) returns the product of the negative
  elements of C.

  Consider that A is the array |1 4 7|.
                               |2 3 5|

  PRODUCT (A, DIM=1) returns the value (2, 12, 35).

  PRODUCT (A, DIM=2) returns the value (28, 30).

138  –  QCMPLX

  QCMPLX (number [,number])

  Class:  Elemental function - Generic

  Converts the argument(s) into a COMPLEX*32 value.

  If one argument is specified, the argument is converted into the
  real part of the complex value and the imaginary part becomes zero.
  If two arguments are specified, the first argument is converted
  into the real part of the complex value and the second argument is
  converted into the imaginary part of the complex value.  If two
  arguments are specified, they must have the same data type.

  +-------+----------+----------+------------+-------------+
  | Args  | Generic  | Specific |  Argument  | Result Type |
  +-------+----------+----------+------------+-------------+
  | 1,2   | QCMPLX   |   --     | INTEGER*1  | COMPLEX*32  |
  | 1,2   |          |   --     | INTEGER*2  | COMPLEX*32  |
  | 1,2   |          |   --     | INTEGER*4  | COMPLEX*32  |
  | 1,2   |          |   --     | INTEGER*8  | COMPLEX*32  |
  | 1,2   |          |   --     | REAL*4     | COMPLEX*32  |
  | 1,2   |          |   --     | REAL*8     | COMPLEX*32  |
  | 1,2   |          |   --     | REAL*16    | COMPLEX*32  |
  |  1    |          |   --     | COMPLEX*8  | COMPLEX*32  |
  |  1    |          |   --     | COMPLEX*16 | COMPLEX*32  |
  |  1    |          |   --     | COMPLEX*32 | COMPLEX*32  |
  +-------+----------+----------+------------+-------------+

  This function cannot be passed as an actual argument.

139  –  QEXT

  QEXT (number)

  Class:  Elemental function - Generic

  Converts the argument to a REAL*16 value.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  QEXT   |  --      | INTEGER*2  | REAL*16     |
  |      |         |  --      | INTEGER*4  | REAL*16     |
  |      |         | QEXT     | REAL*4     | REAL*16     |
  |      |         | QEXTD    | REAL*8     | REAL*16     |
  |      |         |  --      | REAL*16    | REAL*16     |
  |      |         |  --      | COMPLEX*8  | REAL*16     |
  |      |         |  --      | COMPLEX*16 | REAL*16     |
  |      |         |  --      | COMPLEX*32 | REAL*16     |
  +------+---------+----------+------------+-------------+

  These functions cannot be passed as actual arguments.

140  –  QFLOAT

  QFLOAT (integer)

  Class:  Elemental function - Generic

  Converts an integer value to a REAL*16 value.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   | QFLOAT  |  --      | INTEGER*2  | REAL*16     |
  |      |         |  --      | INTEGER*4  | REAL*16     |
  +------+---------+----------+------------+-------------+

141  –  QREAL

  QREAL (dbl-complex-number)

  Class:  Elemental function - Specific

  Converts the real part of a COMPLEX*32 argument to REAL*16 type.

  This function cannot be passed as an actual argument.

142  –  RADIX

  RADIX (number)

  Class:  Inquiry function - Generic

  Returns the base of the model representing numbers of the same type
  and kind type parameter as the argument.

  The "number" can be of integer or real type; it can be scalar or
  array valued.

  The result is a scalar of type default integer.  For an integer
  argument, the result has the value "r" as defined in the integer
  model.  For a real argument, the result has the value "b" as
  defined in the real model.

  For information on integer and real models, see the HP Fortran for
  OpenVMS Language Reference Manual.

  Examples:

  If X is a REAL*4 value, RADIX (X) has the value 2.

143  –  RAN

  RAN (seed)

  Class:  Nonelemental function - Specific

  Generates a general random number of the multiplicative
  congruential type.  This function returns a different REAL*4 number
  between 0.0 (inclusive) and 1.0 (exclusive) each time it is
  invoked.  The argument must be an INTEGER*4 variable or array
  element.

  For best results, you should initialize the argument to a large,
  odd value before invoking RAN the first time.  To generate
  different sets of random values, initialize the seed to a different
  value on each run.  Do not modify the seed during a run.

  This function cannot be passed as an actual argument.

144  –  RANDOM_NUMBER

  RANDOM_NUMBER (real-number)

  Class:  Subroutine

  Returns one pseudorandom number (or an array of such numbers).  The
  argument is set to contain pseudorandom numbers from the uniform
  distribution within the range 0 <= x < 1.

  Examples:

  Consider the following:

  REAL Y, Z (5, 5)
  ! Initialize Y with a pseudorandom number
  CALL RANDOM_NUMBER (HARVEST = Y)
  CALL RANDOM_NUMBER (Z)

  Y and Z contain uniformly distributed random numbers.

145  –  RANDOM_SEED

  RANDOM_SEED ([size] [, put] [, get])

  Class:  Subroutine

  Changes or queries the seed (starting point) for the pseudorandom
  number generator used by RANDOM_NUMBER.  No more than one argument
  can be specified.  If an argument is specified, it must be of
  default integer type.

  The "size" must be scalar; it is set to the number of integers (N)
  that the processor uses to hold the value of the seed.

  The "put" must be an array of rank 1 and size >= N; it is used to
  reset the value of the seed.

  The "get" must be an array of rank 1 and size >= N; it is set to
  the current value of the seed.

  If no argument is specified, a random number based on the date and
  time is assigned to the seed.

  Example:

  Consider the following:

  CALL RANDOM_SEED ( )                   ! Processor reinitializes the
                                         !  seed randomly from the date
                                         !  and time
  CALL RANDOM_SEED (SIZE = M)            ! Sets M to N
  CALL RANDOM_SEED (PUT = SEED (1 : M))  ! Sets user seed
  CALL RANDOM_SEED (GET = OLD  (1 : M))  ! Reads current seed

146  –  RANDU

  RANDU (integer-1, integer-2, store)

  Class:  Subroutine

  Computes a pseudorandom number as a single-precision value.

  The integer arguments must be INTEGER(KIND=2) variables or array
  elements that contain the seed for computing the random number.
  The new seed for computing the next random number is stored into
  these integer arguments.  The "store" is a REAL(KIND=4) variable or
  array element where the computed random number is returned.

  The result is returned in "store", which must be of type
  REAL(KIND=4).  The result value is a pseudorandom number in the
  range 0.0 to 1.0.  The algorithm for computing the random number
  value is based on the values for "integer-1" and "integer-2".

  Example:

  Consider the following:

  REAL X
  INTEGER(2) I, J
  ...
  CALL RANDU (I, J, X)

  If I and J are values 4 and 6, X stores the value 5.4932479E-04.

147  –  RANGE

  RANGE (number)

  Class:  Inquiry function - Generic

  Returns the decimal exponent range in the model representing
  numbers with the same kind type parameter as the argument.

  The argument can be of type integer, real, or complex.  It can be
  scalar or array valued.

  The result is a scalar of type default integer.  For an integer
  argument, the result has the value INT (LOG10 ( HUGE("number") )).
  For a real or complex argument, the result has the value INT(MIN
  (LOG10( HUGE("number") ), -LOG10( TINY("number") ))).

  For information on the integer and real models, see the HP Fortran
  for OpenVMS Language Reference Manual.

  Example:

  If X is a REAL*4 value, RANGE (X) has the value 37.  (HUGE(X) = (1
  - 2**-24) x 2**128 and TINY(X) = 2**-126.)

148  –  REAL

  REAL (number [,kind])

  Class:  Elemental function - Generic

  Converts the argument to a real value.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  REAL   |  --      | INTEGER*1  | REAL*4      |
  |      |         | FLOATI   | INTEGER*2  | REAL*4      |
  |      |see note1| FLOAT    | INTEGER*4  | REAL*4      |
  |      |         | REAL     | INTEGER*4  | REAL*4      |
  |      |         | FLOATK   | INTEGER*8  | REAL*4      |
  |      |         |  --      | REAL*4     | REAL*4      |
  |      |see note2| SNGL     | REAL*8     | REAL*4      |
  |      |         | SNGLQ    | REAL*16    | REAL*4      |
  |      |         |  --      | COMPLEX*8  | REAL*4      |
  |      |         |  --      | COMPLEX*16 | REAL*4      |
  +------+---------+----------+------------+-------------+

  Note1: Or FLOATJ. For compatibility with older versions of
         Fortran, FLOAT can also be specified as a generic
         function.
  Note2: For compatibility with older versions of
         Fortran, SNGL can also be specified as a generic
         function. The generic SNGL includes specific
         function REAL, which takes a REAL*4 argument and
         produces a REAL*4 result.

  These functions cannot be passed as actual arguments.

  REAL is also a specific name for a function that returns the real
  part of a complex number.  The argument must be a COMPLEX*8 data
  type.  The result is a REAL*4 data type.

  The setting of compiler options specifying real size can affect
  FLOAT, REAL, and SNGL.

149  –  REPEAT

  REPEAT (string, ncopies)

  Class:  Transformational function - Generic

  Concatenates several copies of a string.  The kind type parameter
  is the same as "string".  The value of the result is the
  concatenation of "ncopies" copies of "string".

  Examples:

  REPEAT ('S', 3) has the value SSS.

  REPEAT ('ABC', 0) has the value of a zero-length string.

150  –  RESHAPE

  RESHAPE (source, shape [,pad] [,order])

  Class:  Transformational function - Generic

  Constructs an array with a different shape from the argument
  "source" array.

  The size of the "source" array must be >= PRODUCT(shape) if "pad"
  is absent or has size zero.  The "shape" must be an integer array
  of up to 7 elements, with rank one and constant size.  Its size
  must be positive; its elements must not have negative values.  The
  "pad" must be an array of the same type and kind type parameters as
  "source".  It is used to fill in extra values if the result array
  is larger than "source".  The "order" must be an integer array with
  the same shape as "shape".

  The result is an array of shape "shape" with the same type and kind
  type parameters as "source".  The size of the result is the product
  of the values of the elements of "shape".

  In the result array, the array elements of "source" are placed in
  the order of dimensions specified by "order".  If "order" is
  omitted, the array elements are placed in normal array element
  order.

  The array elements of "source" are followed (if necessary) by the
  array elements of "pad" in array element order.  If necessary,
  additional copies of "pad" follow until all the elements of the
  result array have values.

  Examples:

  RESHAPE ((/3, 4, 5, 6, 7, 8/), (/2, 3/)) has the value

   |3 5 7|.
   |4 6 8|.

  RESHAPE ((/3, 4, 5, 6, 7, 8/), (/2, 4/), (/1, 1/), (/2, 1/)) has
  the value

   |3 4 5 6|.
   |7 8 1 1|

151  –  RRSPACING

  RRSPACING (real-number)

  Class:  Elemental function - Generic

  Returns the reciprocal of the relative spacing of model numbers
  near the argument value.

  The result type is the same as the argument.  For information on
  the model for real numbers, see the HP Fortran for OpenVMS Language
  Reference Manual.

  Example:

  If -3.0 is a REAL*4 value, RRSPACING (-3.0) has the value 0.75 x
  2**24.

152  –  SCALE

  SCALE (real-number, integer)

  Class:  Elemental function - Generic

  Returns the value of the exponent part (of the model for the
  argument) changed by a specified value.

  The result type is the same as the "real-number" argument.  For
  information on the real model, see the HP Fortran for OpenVMS
  Language Reference Manual.

  Examples:

  If 3.0 is a REAL*4 value, SCALE (3.0, 2) has the value 12.0 and
  SCALE (3.0, 3) has the value 24.0.

153  –  SCAN

  SCAN (string, set [,back] [,kind])

  Class:  Elemental function - Generic

  Scans a string for any character in a set of characters.  The "set"
  is of type character (the same type as "string").  The "back" is of
  type logical.  The "kind" must be a scalar integer initialization
  expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "back" is absent (or is present with the value false) and
  "string" has at least one character that is in "set", the value of
  the result is the position of the leftmost character of "string"
  that is in "set".

  If "back" is present with the value true and "string" has at least
  one character that is in "set", the value of the result is the
  position of the rightmost character of "string" that is in "set".

  If no character of "string" is in "set" or the length of "string"
  or "set" is zero, the value of the result is zero.

  Examples:

  SCAN ('ASTRING', 'ST') has the value 2.

  SCAN ('ASTRING', 'ST', BACK=.TRUE.) has the value 3.

  SCAN ('ASTRING', 'CD') has the value zero.

154  –  SECNDS

  SECNDS (real-number)

  Class:  Elemental function - Specific

  Returns the number of seconds since midnight minus the value of the
  argument.  The argument must be a REAL*4 data type.  The return
  value is a REAL*4 data type.  The time returned is accurate to .01
  seconds.

  This function cannot be passed as an actual argument.

155  –  SELECTED_INT_KIND

  SELECTED_INT_KIND (integer)

  Class:  Transformational function - Generic

  Returns the value of the kind type parameter of an integer data
  type.

  The result is a scalar of type default integer.

  Example:

  SELECTED_INT_KIND (6) = 4

156  –  SELECTED_REAL_KIND

  SELECTED_REAL_KIND ([integer-p] [,integer-r])

  Class:  Transformational function - Generic

  Returns the value of the kind type parameter of a real data type.

  The "integer-p" specifies decimal precision.  The "integer-r"
  specifies decimal exponent range.  At least one argument must be
  specified.

  The result is a scalar of type default integer.

  Example:

  SELECTED_REAL_KIND (6, 70) = 8

157  –  SET_EXPONENT

  SET_EXPONENT (real-number, integer)

  Class:  Elemental function - Generic

  Returns a copy of "real-number" with the value of the exponent
  part (of the model for the argument) set to a specified value.

  The result type is the same as the "real-number" argument.  For
  information on the real model,see the HP Fortran for OpenVMS
  Language Reference Manual.

  Example:

  If 3.0 is a REAL*4 value, SET_EXPONENT (3.0, 1) has the value 1.5.

158  –  SHAPE

  SHAPE (source [,kind])

  Class:  Inquiry function - Generic

  Returns the shape of an array or scalar argument.

  The "source" must not be an assumed-size array, a disassociated
  pointer, or an allocatable array that is not allocated.  The "kind"
  must be a scalar integer initialization expression.

  The result is a rank-one integer array whose size is equal to the
  rank of "source".  If "kind" is present, the kind parameter of the
  result is that specified by "kind"; otherwise, the kind parameter
  of the result is that of default integer.  If the processor cannot
  represent the result value in the kind of the result, the result is
  undefined.

  The value of the result is the shape of "source".

  The setting of compiler options that specify integer size can
  affect the result of this function.

  Examples:

  SHAPE (2) has the value of a rank-one array of size zero.

  If B is declared as B(2:4, -3:1), then SHAPE (B) has the value (3,
  5).

159  –  SIGN

  SIGN (arg1, sign-arg2)

  Class:  Elemental function - Generic

  Assigns the sign of the second argument to the absolute value of
  the first.

  If the second argument is of type real and zero, the value of the
  result is |arg1|.  However, if the processor can distinguish
  between positive and negative real zero and the compiler option
  /ASSUME=MINUS0 is specified, the following occurs:

   o  If the second argument is positive real zero, the value of the
      result is |arg1|.

   o  If the second argument is negative real zero, the value of the
      result is -|arg1|.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  2   |  SIGN   |  --      | INTEGER*1  | INTEGER*1   |
  |      |         | IISIGN   | INTEGER*2  | INTEGER*2   |
  |      |see note | ISIGN    | INTEGER*4  | INTEGER*4   |
  |      |         | KISIGN   | INTEGER*8  | INTEGER*8   |
  |      |         | SIGN     | REAL*4     | REAL*4      |
  |      |         | DSIGN    | REAL*8     | REAL*8      |
  |      |         | QSIGN    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

  NOTE: Or JISIGN.  For compatibility with older versions
        of Fortran, ISIGN can also be specified as a generic
        function.

160  –  SIN

  SIN (number)

  Class:  Elemental function - Generic

  Returns the sine of the argument.  The argument must be in radians;
  it is treated modulo 2*pi.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  SIN    | SIN      | REAL*4     | REAL*4      |
  |      |         | DSIN     | REAL*8     | REAL*8      |
  |      |         | QSIN     | REAL*16    | REAL*16     |
  |      |see note | CSIN     | COMPLEX*8  | COMPLEX*8   |
  |      |         | CDSIN    | COMPLEX*16 | COMPLEX*16  |
  |      |         | ZSIN     | COMPLEX*16 | COMPLEX*16  |
  |      |         | CQSIN    | COMPLEX*32 | COMPLEX*16  |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect CSIN.

161  –  SIND

  SIND (number)

  Class:  Elemental function - Generic

  Returns the sine of the argument.  The argument must be in degrees;
  it is treated modulo 360.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  SIND   | SIND     | REAL*4     | REAL*4      |
  |      |         | DSIND    | REAL*8     | REAL*8      |
  |      |         | QSIND    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

162  –  SINH

  SINH (number)

  Class:  Elemental function - Generic

  Returns the hyperbolic sine of the argument.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  SINH   | SINH     | REAL*4     | REAL*4      |
  |      |         | DSINH    | REAL*8     | REAL*8      |
  |      |         | QSINH    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

163  –  SIZE

  SIZE (array [,dim] [,kind])

  Class:  Inquiry function - Generic

  Returns the total number of elements in an array, or the extent of
  an array along a specified dimension.

  The "array" must not be a disassociated pointer or an allocatable
  array that is not allocated.  It can be an assumed-size array if
  "dim" is present with a value less than the rank of "array".  The
  "dim" must be a scalar integer with a value in the range 1 to n,
  where "n" is the rank of "array".  The "kind" must be a scalar
  integer initialization expression.

  The result is a scalar of type integer.  If "kind" is present, the
  kind parameter of the result is that specified by "kind";
  otherwise, the kind parameter of the result is that of default
  integer.  If the processor cannot represent the result value in the
  kind of the result, the result is undefined.

  If "dim" is present, the result is the extent of dimension "dim" in
  "array"; otherwise, the result is the total number of elements in
  "array".

  The setting of compiler options that specify integer size can
  affect the result of this function.

  Example:

  If B is declared as B(2:4, -3:1), then SIZE (B, DIM=2) has the
  value 5 and SIZE (B) has the value 15.

164  –  SIZEOF

  SIZEOF (arg)

  Class:  Elemental function - Specific

  Returns the number of bytes of storage used by the argument.
  +------+---------+----------+------------------+-------------+
  | Args | Generic | Specific |    Argument      | Result Type |
  +------+---------+----------+------------------+-------------+
  |   1  |   --    | SIZEOF   | Anything with a  | INTEGER*8   |
  |      |         |   --     | valid data type, |             |
  |      |         |          | except assumed-  |             |
  |      |         |          | size arrays.     |             |
  +------+---------+----------+------------------+-------------+

  This function cannot be passed as an actual argument.

165  –  SPACING

  SPACING (real-number)

  Class:  Elemental function - Generic

  Returns the absolute spacing of model numbers near the argument
  value.  The result type is the same as the argument.

  Example:

  If 3.0 is a REAL*4 value, SPACING (3.0) has the value 2**-22.

166  –  SPREAD

  SPREAD (source, dim, ncopies)

  Class:  Transformational function - Generic

  Creates a replicated array with an added dimension by making copies
  of existing elements along a specified dimension.

  The "source" can be an array or scalar.  The "dim" is a scalar of
  type integer.  It must have a value in the range 1 to n +
  1(inclusive), where "n" is the rank of "source".  The integer
  scalar "ncopies" becomes the extent of the added dimension in the
  result.

  The result is an array of the same type as "source" and of rank
  that is one greater than "source".

  If "source" is an "array", each array element in dimension "dim" of
  the result is equal to the corresponding array element in "source".

  If "source" is a scalar, the result is a rank-one array with
  "ncopies" elements, each with the value "source".

  Examples:

  SPREAD ("B", 1, 4) is the character array (/"B", "B", "B", "B"/).

  B is the array (3, 4, 5) and NC has the value 4.

  SPREAD (B, DIM=1, NCOPIES=NC) produces the array

   |3 4 5|
   |3 4 5|.
   |3 4 5|
   |3 4 5|

  SPREAD (B, DIM=2, NCOPIES=NC) produces the array

   |3 3 3 3|
   |4 4 4 4|.
   |5 5 5 5|

167  –  SNGL

  See the REAL function.

168  –  SQRT

  SQRT (number)

  Class:  Elemental function - Generic

  Returns the square root of the argument.

  If the argument is real, its value must be greater than or equal to
  zero.
  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  SQRT   | SQRT     | REAL*4     | REAL*4      |
  |      |         | DSQRT    | REAL*8     | REAL*8      |
  |      |         | QSQRT    | REAL*16    | REAL*16     |
  |      |see note | CSQRT    | COMPLEX*8  | COMPLEX*8   |
  |      |         | CDSQRT   | COMPLEX*16 | COMPLEX*8   |
  |      |         | ZSQRT    | COMPLEX*16 | COMPLEX*8   |
  |      |         | CQSQRT   | COMPLEX*32 | COMPLEX*8   |
  +------+---------+----------+------------+-------------+

  Note: The setting of compiler options specifying real
        size can affect CSQRT.

  The result of CSQRT, CDSQRT, and ZSQRT is the principal value, with
  the real part greater than or equal to zero.  If the real part is
  zero, the result is the principal value, with the imaginary part
  greater than or equal to zero.

169  –  SUM

  SUM (array [,dim] [,mask])

  Class:  Transformational function - Generic

  Returns the sum of all the elements in an entire array or in a
  specified dimension of an array.

  The "array" can be of integer or real type.  The "dim" is optional
  and must be a scalar integer with a value in the range 1 to n,
  where "n" is the rank of "array".  The "mask" is optional and must
  be a logical array that is conformable with "array".

  The result is the same data type as "array".  The result is a
  scalar if "dim" is absent or "array" has rank one.  Otherwise, the
  result is an array with rank that is one less than "array", and
  shape (d1, d2,..., d"dim"-1, d"dim"+1,..., dn), where (d1, d2,...,
  dn) is the shape of "array".

  If only "array" appears, the result is the sum of all elements of
  "array".  If "array" has size zero, the result is zero.

  If "array" and "mask" both appear, the result is the sum of all
  elements of "array" corresponding to true elements of "mask".  If
  "array" has size zero, or every element of "mask" has the value
  .FALSE., the result is zero.

  If "dim" also appears and "array" has rank one, the value is the
  same as SUM (array [,mask=mask]).  Otherwise, the value of element
  (s1, s2,..., s"dim"-1, s"dim"+1,..., sn) of SUM (array, dim,
  [,mask]) is equal to SUM (array (s1, s2,..., s"dim"-1, :, s"dim"+1,
  ..., sn)) [mask=mask (s1, s2, ..., s"dim"-1, :, s "dim"+1 ...,
  sn)].

  Examples:

  SUM ((/2, 3, 4/)) and SUM ((/2, 3, 4/), DIM=1) returns the value 9.

  SUM (B, MASK=B .LT.  0.0) returns the arithmetic sum of the
  negative elements of B.

  Consider that C is the array:

   |1 2 3|
   |4 5 6|.

  SUM (C, DIM=1) returns the value (5, 7, 9).

  SUM (C, DIM=2) returns the value (6, 15).

170  –  SYSTEM_CLOCK

  SYSTEM_CLOCK ([count] [,count-rate] [,count-max])

  Class:  Subroutine

  Returns integer data from a real-time clock.

  All arguments are scalar of type default integer.  The "clock" is
  set to a value based on the current value of the processor clock.
  The value is increased by one for each clock count until the value
  "countmax" is reached, and is reset to zero at the next count.
  ("count" lies in the range 0 to "countmax".) The "count-rate" is set
  to the number of processor clock counts per second modified by the
  kind of "count-rate." See the HP Fortran for OpenVMS Language
  Reference Manual.

  SYSTEM_CLOCK returns the number of seconds from 00:00 Coordinated
  Universal Time (CUT) 1 JAN 1970.  The number is returned with no
  bias.  To get the elapsed time, you must call SYSTEM_CLOCK twice,
  and subtract the starting time value from the ending time value.

  Examples:

  Consider the following:

    INTEGER(2) :: IC2, CRATE2, CMAX2
    INTEGER(4) :: IC4, CRATE4, CMAX4
    CALL SYSTEM_CLOCK(COUNT=IC2, COUNT_RATE=CRATE2, COUNT_MAX=CMAX2)
    CALL SYSTEM_CLOCK(COUNT=IC4, COUNT_RATE=CRATE4, COUNT_MAX=CMAX4)
    PRINT *, IC2, CRATE2, CMAX2
    PRINT *, IC4, CRATE4, CMAX4
    END

  This program was run on Thursday Dec 11, 1997 at 14:23:55 EST and
  produced the following output:
    13880   1000  32767
    1129498807       10000  2147483647

171  –  TAN

  TAN (real-number)

  Class:  Elemental function - Generic

  Returns the tangent of the argument.  The argument must be in
  radians; it is treated modulo 2*pi.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  TAN    | TAN      | REAL*4     | REAL*4      |
  |      |         | DTAN     | REAL*8     | REAL*8      |
  |      |         | QTAN     | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

172  –  TAND

  TAND (real-number)

  Class:  Elemental function - Generic

  Returns the tangent of the argument.  The argument must be in
  degrees; it is treated modulo 360.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  TAND   | TAND     | REAL*4     | REAL*4      |
  |      |         | DTAND    | REAL*8     | REAL*8      |
  |      |         | QTAND    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

173  –  TANH

  TANH (real-number)

  Class:  Elemental function - Generic

  Returns the hyperbolic tangent of the argument.

  +------+---------+----------+------------+-------------+
  | Args | Generic | Specific |  Argument  | Result Type |
  +------+---------+----------+------------+-------------+
  |  1   |  TANH   | TANH     | REAL*4     | REAL*4      |
  |      |         | DTANH    | REAL*8     | REAL*8      |
  |      |         | QTANH    | REAL*16    | REAL*16     |
  +------+---------+----------+------------+-------------+

174  –  TIME

  TIME (buf)

  Class:  Elemental function

  Places the current time in 24-hour ASCII format in the argument.
  The time is returned as an 8-byte ASCII character string having the
  following form:

     hh:mm:ss

  A 24-hour clock is used.

  The "buf" is an 8-byte variable, array, array element, or character
  substring.  If "buf" is numeric type and smaller than 8 bytes, data
  corruption can occur.

  If "buf" is character type, its associated length is passed to the
  subroutine.  If "buf" is smaller than 8 bytes, the subroutine
  truncates the date to fit in the specified length.  Note that if a
  CHARACTER array is passed, the subroutine stores the time in the
  first array element, using the element length, not the length of
  the entire array.  For example, consider the following:

  CHARACTER*1 HOUR(8)
  ...
  CALL TIME(HOUR)

  The length of the first array element in CHARACTER array HOUR is
  passed to the TIME subroutine.  The subroutine then truncates the
  time to fit into the one-character element, producing an incorrect
  result.

175  –  TINY

  TINY (real-number)

  Class:  Inquiry function - Generic

  Returns the smallest number in the model representing the same type
  and kind type parameter as the argument.

  The argument must be of type real; it can be scalar or array
  valued.  The result type is scalar of the same type and kind type
  parameter as the argument.  The real model is described in the
  HP Fortran for OpenVMS Language Reference Manual.

  Examples:

  If X is of type REAL*4, TINY (X) has the value 2**-126.

176  –  TRAILZ

  TRAILZ (integer)

  Class:  Elemental function - Generic

  Returns the number of trailing zeros in the binary representation
  of the integer argument.  The result type is the same as the
  argument.

  Example:

  Consider the following:

    INTEGER*8 J, TWO
    PARAMETER (TWO=2)
    DO J= -1, 40
      TYPE *, TRAILZ(TWO**J)  ! Prints 64, then 0 up to
    ENDDO                     !   40 (trailing zeros)
    END

177  –  TRANSFER

  TRANSFER (source, mold [,size])

  Class:  Transformational function - Generic

  Copies the bit pattern of "source" and interprets it according to
  the type and kind type parameters of "mold".

  The "source" and "mold" can be of any type; they can be scalar or
  array valued.  The "mold" provides the type characteristics (not a
  value) for the result.  The "size" must be scalar of type integer;
  it provides the number of elements for the output result.

  If "mold" is a scalar and "size" is absent, the result is a scalar.

  If "mold" is an array and "size" is absent, the result is a
  rank-one array.  Its size is the smallest that is possible to hold
  all of "source".

  If "size" is present, the result is a rank-one array of size
  "size".

  If the physical representation of the result is larger than
  "source", the result contains "source"'s bit pattern in its
  right-most bits; the left-most bits of the result are undefined.

  If the physical representation of the result is smaller than
  "source", the result contains the right-most bits of "source"'s bit
  pattern.

  Examples:

  TRANSFER (1082130432, 0.0) has the value 4.0 (on processors that
  represent the values 4.0 and 1082130432 as the string of binary
  digits 0100 0000 1000 0000 0000 0000 0000 0000).

  TRANSFER ((/2.2, 3.3, 4.4/), ((0.0, 0.0))) results in a scalar
  whose value is (2.2, 3.3).

  TRANSFER ((/2.2, 3.3, 4.4/), (/(0.0, 0.0)/)) results in a complex
  rank-one array of length 2.  Its first element is (2.2,3.3) and its
  second element has a real part with the value 4.4 and an undefined
  imaginary part.

  TRANSFER ((/2.2, 3.3, 4.4/), (/(0.0, 0.0)/), 1) results in a
  complex rank-one array having one element with the value (2.2,
  3.3).

178  –  TRANSPOSE

  TRANSPOSE (matrix)

  Class:  Transformational function - Generic

  Transposes an array of rank two (can be any data type).

  The result is a rank-two array with the same type and kind type
  parameters as "matrix".  Its shape is (n, m), where (m, n) is the
  shape of "matrix".  For example, if the shape of "matrix" is (4,6),
  the shape of the result is (6,4).

  Element (i, j) of the result has the value matrix(j, i), where "i"
  is in the range 1 to n, and "j" is in the range 1 to m.

  Examples:

  Consider that B is the array:

   |2 3 4|
   |5 6 7|.
   |8 9 1|

  TRANSPOSE (B) has the value

   |2 5 8|
   |3 6 9|.
   |4 7 1|

179  –  TRIM

  TRIM (string)

  Class:  Transformational function - Generic

  Returns the argument with trailing blanks removed.

  The "string" is a scalar of type character.  The result is of type
  character with the same kind type parameter as "string".  Its
  length is the length of "string" minus the number of trailing
  blanks in "string".

  The value of the result is the same as "string", except any
  trailing blanks are removed.  If "string" contains only blank
  characters, the result has zero length.

  Examples:

  TRIM ('  NAME    ') has the value '  NAME'.

  TRIM ('  C  D     ') has the value '  C  D'.

180  –  UBOUND

  UBOUND (array [,dim] [,kind])

  Class:  Inquiry function - Generic

  Returns the upper bounds for all dimensions of an array, or the
  upper bound for a specified dimension.

  The "array" cannot be an allocatable array that is not allocated,
  or a disassociated pointer.  The "dim" is a scalar integer with a
  value in the range 1 to n, where "n" is the rank of "array".  The
  "kind" must be a scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "dim" is present, the result is a scalar.  Otherwise, the result
  is a rank-one array with one element for each dimension of "array".
  Each element in the result corresponds to a dimension of "array".

  If "array" is an array section or an array expression that is not a
  whole array or array structure component, UBOUND (array,dim) has a
  value equal to the number of elements in the given dimension.

  The setting of compiler options that specify integer size can
  affect the result of this function.

  Examples:

  Consider the following:

  REAL ARRAY_A (1:3, 5:8)
  REAL ARRAY_B (2:8, -3:20)

  UBOUND (ARRAY_A) is (3, 8).  UBOUND (ARRAY_A, DIM=2) is 8.

  UBOUND (ARRAY_B) is (8, 20).  UBOUND (ARRAY_B (5:8, :)) is (4,24)
  because the number of elements is significant for array section
  arguments.

181  –  UNPACK

  UNPACK (vector, mask, field)

  Class:  Transformational function - Generic

  Takes elements from a rank-one array and unpacks them into another
  (possibly larger) array under the control of a mask.

  The "vector" must be a rank-one array of any type.  Its size must
  be at least t, where "t" is the number of true elements in "mask".
  The "mask" must be of logical type; it determines where elements of
  "vector" are placed when they are unpacked.

  The "field" must be of the same type and type parameters as
  "vector" and conformable with "mask".  Elements in "field" are
  inserted into the result array when the corresponding "mask"
  element has the value false.

  The result is an array with the same shape as "mask", and the same
  type and type parameters as "vector".

  Elements in the result array are filled in array element order.  If
  element i of the result is true, the corresponding element of the
  result is filled by the next element in "vector".

  Examples:

  Consider that N is the array |0 0 1|, P is the array (2, 3, 4, 5),
                               |1 0 1|
                               |1 0 0|

  and Q is the array |T F F|
                     |F T F|.
                     |T T F|

  UNPACK (P, MASK=Q, FIELD=N) produces the result

   |2 0 1|
   |1 4 1|.
   |3 5 0|

  UNPACK (P, MASK=Q, FIELD=1) produces the result

   |2 1 1|
   |1 4 1|.
   |3 5 1|

182  –  VERIFY

  VERIFY (string, set [,back] [,kind])

  Class:  Elemental function - Generic

  Verifies that a set of characters contains all the characters in a
  string by identifying the first character in the string that is not
  in the set.

  The "set" must be of type character with the same kind type
  parameter as "string".  The "back" must be of type logical.  The
  "kind" must be a scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.

  If "back" is absent (or is present with the value false) and
  "string" has at least one character that is not in "set", the value
  of the result is the position of the leftmost character of "string"
  that is not in "set".

  If "back" is present with the value true and "string" has at least
  one character that is not in "set", the value of the result is the
  position of the rightmost character of "string" that is not in
  "set".

  If each character of "string" is in "set" or the length of "string"
  is zero, the value of the result is zero.

  Examples:

  VERIFY ('CDDDC', 'C') has the value 2.

  VERIFY ('CDDDC', 'C', BACK=.TRUE.) has the value 4.

  VERIFY ('CDDDC', 'CD') has the value zero.

183  –  ZEXT

  ZEXT (integer [,kind])

  Class:  Elemental function - Generic

  Returns the value of the argument, zero extended.

  The "kind" must be a scalar integer initialization expression.

  The result is of type integer.  If "kind" is present, the kind
  parameter of the result is that specified by "kind"; otherwise, the
  kind parameter of the result is that of default integer.  If the
  processor cannot represent the result value in the kind of the
  result, the result is undefined.
  +------+----------+----------+------------+-------------+
  | Args | Generic  | Specific |  Argument  | Result Type |
  +------+----------+----------+------------+-------------+
  |  1   |  ZEXT    | IZEXT    | LOGICAL*1  | INTEGER*2   |
  |      |          |  --      | LOGICAL*2  | INTEGER*2   |
  |      |          |  --      | INTEGER*1  | INTEGER*2   |
  |      |          |  --      | INTEGER*2  | INTEGER*2   |
  |      |          | JZEXT    | LOGICAL*1  | INTEGER*4   |
  |      |          |  --      | LOGICAL*2  | INTEGER*4   |
  |      |          |  --      | LOGICAL*4  | INTEGER*4   |
  |      |          |  --      | INTEGER*1  | INTEGER*4   |
  |      |          |  --      | INTEGER*2  | INTEGER*4   |
  |      |          |  --      | INTEGER*4  | INTEGER*4   |
  |      |          | KZEXT    | LOGICAL*1  | INTEGER*8   |
  |      |          |  --      | LOGICAL*2  | INTEGER*8   |
  |      |          |  --      | LOGICAL*4  | INTEGER*8   |
  |      |          |  --      | LOGICAL*8  | INTEGER*8   |
  |      |          |  --      | INTEGER*1  | INTEGER*8   |
  |      |          |  --      | INTEGER*2  | INTEGER*8   |
  |      |          |  --      | INTEGER*4  | INTEGER*8   |
  |      |          |  --      | INTEGER*8  | INTEGER*8   |
  +------+----------+----------+------------+-------------+

  The setting of compiler options specifying integer size can affect
  ZEXT.
Close Help