HELPLIB.HLB  —  FORTRAN  Data  Constants
  A constant is a fixed value.  The value of a constant can be a
  numeric value, a logical value, or a character string.

  A constant that has a name is a named constant.  A named constant
  can be of any type, including derived type, and it can be
  array-valued.  A named constant has the PARAMETER attribute and is
  specified in a type declaration statement or PARAMETER statement.

  A constant that does not have a name is a literal constant.  A
  literal constant must be of intrinsic type and it cannot be
  array-valued.

  There are nine types of literal constants:  integer, real, complex,
  binary, octal, hexadecimal, logical, character, and Hollerith.
  Binary, octal, hexadecimal, and Hollerith constants have no data
  type; they assume a data type that conforms to the context in which
  they are used.

1  –  Binary

  You can use this type of constant wherever numeric constants are
  allowed; it assumes a numeric data type according to its context.

  A binary constant has one of these forms:

    B'd[d...]'
    B"d[d...]"

    d   Is a binary (base 2) digit (0 or 1).

  You can specify up to 128 binary digits in a binary constant.

2  –  Character

  A character constant is a string of printable ASCII characters
  enclosed by delimiters.  It takes one of the following forms:

    [k_]'[c...]' [C]
    [k_]"[c...]" [C]

    k  Is an optional kind type parameter (1 is the default).
       It must be followed by an underscore.

    c  Is an ASCII character.

    C  Is a C string specifier.

  If no kind type parameter is specified, the type is default
  character.

  The length of the character constant is the number of characters
  between the delimiters.  In the apostrophe format, two consecutive
  apostrophes represent a single apostrophe.  In the quotation mark
  format, two consecutive quotation marks represent a single
  quotation mark.

  The length of a character constant must be in the range 0 to 2000.

2.1  –  C Strings

  String values in the C language are terminated with null characters
  (CHAR(0)) and can contain nonprintable characters (such as a
  backspace).

  Nonprintable characters are specified by escape sequences.  An
  escape sequence is denoted by using the backslash (\) as an escape
  character, followed by a single character indicating the
  nonprintable character desired.

  This type of string is specified by using a standard string
  constant followed by the character C.  The standard string constant
  is then interpreted as a C-language constant.  Backslashes are
  treated as escapes, and a null character is automatically appended
  to the end of the string (even if the string already ends in a null
  character).

  The following C-style escape sequences are allowed in character
  constants:

     Escape Sequence      Represents
     ---------------      ----------
     \a or \A             A bell
     \b or \B             A backspace
     \f or \F             A formfeed
     \n or \N             A new line
     \r or \R             A carriage return
     \t or \T             A horizontal tab
     \v or \V             A vertical tab
     \x"hh" or \X"hh"     A hexadecimal bit pattern
     \"ooo"               An octal bit pattern
     \0                   A null character
     \\                   A backslash

  If a character constant contains any other escape sequence, the
  backslash is ignored.

  A C string must also be a valid Fortran string.  If the string is
  delimited by apostrophes, apostrophes in the string itself must be
  represented by two consecutive apostrophes ('').

  For example, the escape sequence \'string causes a compiler error
  because Fortran interprets the apostrophe as the end of the string.
  The correct form is \''string.

  If the string is delimited by quotation marks, quotation marks in
  the string itself must be represented by two consecutive quotation
  marks ("").

  The sequences \"ooo" and \x"hh" allow any ASCII character to be
  given as a one- to three-digit octal or a one- to two-digit
  hexadecimal character code.  Each octal digit must be in the range
  0 to 7, and each hexadecimal digit must be in the range 0 to F.
  For example, the C strings '\010'C and '\x08'C) both represent a
  backspace character followed by a null character.

  The C string '\\abcd'C) is equivalent to the string '\abcd' with a
  null character appended.  The string ''C represents the ASCII null
  character.

3  –  Complex

  A complex constant consists of a pair of real or integer constants.
  The two constants are separated by a comma and enclosed in
  parentheses.  The first constant represents the real part of the
  number and the second constant represents the imaginary part.

  VSI Fortran provides three kind type parameters for data of type
  complex:  COMPLEX(KIND=4) (or COMPLEX*8), COMPLEX(KIND=8) (or
  COMPLEX*16), and COMPLEX(KIND=16).  COMPLEX(KIND=8) is DOUBLE
  COMPLEX.  The type specifier for the complex type is COMPLEX; the
  type specifier for the double complex type is DOUBLE COMPLEX.

  If a kind type parameter is specified, the complex constant has the
  kind specified.  If no kind type parameter is specified, the kind
  type of both parts is default real, and the constant is of type
  default complex.

  A COMPLEX (COMPLEX(KIND=4) or COMPLEX*8) constant has
  the form:

   (c,c)

    c   Is an integer or REAL (REAL(KIND=4) or REAL*4)
        constant

  A DOUBLE COMPLEX (COMPLEX(KIND=8) or COMPLEX*16) constant
  has the form:

   (c,c)

    c   Is an integer, REAL (REAL(KIND=4) or REAL*4), or
        DOUBLE PRECISION (REAL(KIND=8) or REAL*8) constant.
        At least one of the pair must be a DOUBLE PRECISION
        constant.

  A COMPLEX(KIND=16) or COMPLEX*32 constant has the form:

   (c,c)

    c   Is an integer, REAL (REAL(KIND=4) or REAL*4),
        DOUBLE PRECISION (REAL(KIND=8) or REAL*8), or
        REAL (KIND=16) (or REAL*16) constant.  At least
        one of the pair must be a a REAL(KIND=16)constant.

  Note that the comma and parentheses are required.

4  –  Hexadecimal

  You can use this type of constant wherever numeric constants are
  allowed; it assumes a numeric data type according to its context.

  A hexadecimal constant has one of these forms:

    Z'd[d...]'
    Z"d[d...]"

    d   Is a hexadecimal (base 16) digit in the range 0 - 9,
        or a letter in the range A - F, or a - f

  You can specify up to 128 bits in hexadecimal (32 hexadecimal
  digits) constants.  Leading zeros are ignored.

5  –  Hollerith

  A Hollerith constant is a string of printable characters preceded
  by a character count and the letter H.  It is used only in numeric
  expressions and has the form:

    nHc[c...]

    n     Is an unsigned, nonzero integer constant stating the
          number of characters in the string (including tabs
          and spaces).

    c     Is a printable ASCII character.

  A Hollerith constant can be a string of 1 to 2000 characters and is
  stored as a byte string, one character per byte.

  Hollerith constants have no data type, but assume a numeric data
  type according to the context in which they are used.  They assume
  data types according to the following rules:

   o  When the constant is used with a binary operator, including the
      assignment operator, the data type of the constant is the data
      type of the other operand.

   o  When a specific data type is required, that type is assumed for
      the constant.

   o  When the constant is used as an actual argument, no data type
      is assumed.

  When the length of the constant is less than the length implied by
  the data type, blanks are appended to the constant on the right.

  When the length of the constant is greater than the length implied
  by the data type, the constant is truncated on the right.  If any
  characters other than blank characters are truncated, an error
  occurs.

6  –  Integer

  An integer constant is a whole number with no decimal point.  It
  can have a leading sign and is interpreted as a decimal number.

  VSI Fortran provides four kind type parameters for data of type
  integer:  INTEGER(KIND=1) (or INTEGER*1), INTEGER(KIND=2) (or
  INTEGER*2), INTEGER(KIND=4) (or INTEGER*4), and INTEGER(KIND=8) (or
  INTEGER*8).

  The type specifier for the integer type is INTEGER.

  If a kind type parameter is specified, the integer has the kind
  specified.  If a kind type parameter is not specified, integer
  constants are interpreted as follows:

   o  If the integer constant is within the default integer kind, the
      kind is default integer.

   o  If the integer constant is outside the default integer kind,
      the kind type of the integer constant is the smallest integer
      kind which holds the constant.

  Integer constants take the following form:

    [s]n[n...][_k]

    s   Is a sign; required if negative (-), optional if
        positive (+).

    n   Is a decimal digit (0 through 9).  Any leading
        zeros are ignored.

    k   Is an optional kind type parameter (1 for
        INTEGER(KIND=1), 2 for INTEGER(KIND=2), 4 for
        INTEGER(KIND=4), and 8 for INTEGER(KIND=8)). It
        must be preceded by an underscore (_).

  An unsigned constant is assumed to be nonnegative.

  Integers are expressed in decimal values (base 10) by default.

  To specify a constant that is not in base 10, use the following
  syntax:

    [s][[base] #]nnn...

    s     Is a sign; required if negative (-), optional if
          positive (+).

    base  Is any constant from 2 through 36.

  If "base" is omitted but # is specified, the integer is interpreted
  in base 16.  If both "base" and # are omitted, the integer is
  interpreted in base 10.

  For bases 11 through 36, the letters A through Z represent numbers
  greater than 9.  For example, for base 36, A represents 10, B
  represents 11, C represents 12, and so on, through Z, which
  represents 35.  The case of the letters is not significant.

  For example, the following integers are all assigned a value equal
  to 3994575 decimal:

  I     = 2#1111001111001111001111
  K     = #3CF3CF
  n     = +17#2DE110
  index = 36#2DM8F

  You can use integer constants to assign values to data.  The
  integer data types have the following ranges:

    BYTE         Same range as INTEGER*1

    INTEGER*1    Signed integers: -128 to 127 (-2**7 to 2**7-1)
    (1 byte)     Unsigned integers: 0 to 255 (2**8-1)

    INTEGER*2    Signed integers: -32768 to 32767
    (2 bytes)                     (-2**15 to 2**15-1)
                 Unsigned integers: 0 to 65535 (2**16-1)

    INTEGER*4    Signed integers: -2147483648 to 2147483647
    (4 bytes)                          (-2**31 to 2**31-1)
                 Unsigned integers: 0 to 4294967295 (2**32-1)

    INTEGER*8    Signed integers: -9223372036854775808 to
    (8 bytes)    9223372036854775807 (-2**63 to 2**63-1)

  NOTE1: The value of an integer constant must be within
         INTEGER(KIND=8) range.

  NOTE2: The "unsigned" ranges above are allowed for assignment
         to variables of these types, but the data type is
         treated as signed in arithmetic operations.

7  –  Logical

  A logical constant represents only the logical values true or
  false.  It takes one of these forms:

    .TRUE.[_k]
    .FALSE.[_k]

    k   Is an optional kind type parameter (1 for
        LOGICAL(KIND=1), 2 for LOGICAL(KIND=2), 4 for
        LOGICAL(KIND=4), and 8 for LOGICAL(KIND=8)).
        It must be preceded by an underscore (_).

  The type specifier for the logical type is LOGICAL.

  If a kind type parameter is specified, the logical constant has the
  kind specified.  If no kind type parameter is specified, the kind
  type of the constant is default logical.

  Note that logical data type ranges correspond to their comparable
  integer data type ranges.  For example, the LOGICAL*2 range is the
  same as the INTEGER*2 range.

8  –  Octal

  You can use this type of constant wherever numeric constants are
  allowed; it assumes a numeric data type according to its context.

  An octal constant has one of these forms:

    O'd[...d]'
    O"d[...d]"

    d   Is an octal (base 8) digit in the range 0 - 7.

  You can specify up to 128 bits in octal (43 octal digits)
  constants.  Leading zeros are ignored.

9  –  Real

  A real constant approximates the value of a mathematical real
  number.  The value of the constant can be positive, zero, or
  negative.

  VSI Fortran provides three kind type parameters for data of type
  real:  REAL(KIND=4) (or REAL*4), REAL(KIND=8) (or REAL*8), and
  REAL(KIND=16) (or REAL*16).  REAL(KIND=8) is DOUBLE PRECISION.  If
  DOUBLE PRECISION is used, a kind type parameter must not be
  specified for the constant.

  The type specifier for the real (single-precision) type is REAL;
  the type specifier for the double precision type is DOUBLE
  PRECISION.

  If a kind type parameter is specified, the real constant has the
  kind specified.  If a kind type parameter is not specified, the
  kind is default real.

  The following is the general form of a real constant with no
  exponent part:

    [s]n[n...][_k]

  A real constant with an exponent part has one of the following
  forms:

    [s]n[n...]E[s]nn...[_k]
    [s]n[n...]D[s]nn...
    [s]n[n...]Q[s]nn...

     s   Is a sign; required if negative (-), optional if
         positive (+).

     n   Is a decimal digit (0 through 9). A decimal point
         must appear if the real constant has no exponent part.

     k   Is an optional kind type parameter (4 for REAL(KIND=4),
         8 for REAL(KIND=8), or 16 for REAL(KIND=16)).  It must
         be preceded by an underscore (_).

  Leading zeros (zeros to the left of the first nonzero digit) are
  ignored in counting significant digits.  For example, in the
  constant 0.00001234567, all of the nonzero digits, and none of the
  zeros, are significant.  (See the following sections for the number
  of significant digits each kind type parameter typically has).

  The exponent represents a power of 10 by which the preceding real
  or integer constant is to be multiplied (for example, 1.0E6
  represents the value 1.0 * 10**6).

  A real constant with no exponent part is (by default) a
  single-precision (REAL(KIND=4)) constant.  You can change this
  default behavior by specifying the compiler option
  /ASSUME=FPCONSTANT.

  If the real constant has no exponent part, a decimal point must
  appear in the string (anywhere before the optional kind type
  parameter).  If there is an exponent part, a decimal point is
  optional in the string preceding the exponent part; the exponent
  part must not contain a decimal point.

  The exponent letter E denotes a single-precision real (REAL(KIND=4)
  or REAL*4) constant, unless the optional kind type parameter
  specifies otherwise.  For example, -9.E2_8 is a double-precision
  constant (which can also be written as -9.D2).

  The exponent letter D denotes a double-precision real (REAL(KIND=8)
  or REAL*8) constant.

  The exponent letter Q denotes a quad-precision real (REAL(KIND=16)
  or REAL*16) constant.  A minus sign must appear before a negative
  real constant; a plus sign is optional before a positive constant.
  Similarly, a minus sign must appear between the exponent letter (E,
  D, or Q) and a negative exponent, whereas a plus sign is optional
  between the exponent letter and a positive exponent.

  If the real constant includes an exponent letter, the exponent
  field cannot be omitted, but it can be zero.

  To specify a real constant using both an exponent letter and a kind
  type parameter, the exponent letter must be E, and the kind type
  parameter must follow the exponent part.

9.1  –  DOUBLE_PRECISION

  See DATA CONSTANTS REAL REAL_8 in this Help file.

9.2  –  REAL_4

  REAL(KIND=4) or REAL*4

  A single-precision REAL constant occupies four bytes of memory.
  The number of digits is unlimited, but typically only the leftmost
  seven digits are significant.

  Either VAX F_floating or IEEE S_floating format is used, depending
  on the compiler option specified.

9.3  –  REAL_8

  DOUBLE PRECISION (REAL(KIND=8) or REAL*8)

  A DOUBLE PRECISION constant has more than twice the accuracy of a
  REAL number, and greater range.

  A DOUBLE PRECISION constant occupies eight bytes of memory.  The
  number of digits that precede the exponent is unlimited, but
  typically only the leftmost 15 digits are significant.

  Either VAX D_floating, G_floating, or IEEE T_floating format is
  used, depending on the compiler option specified.

9.4  –  REAL_16

  REAL(KIND=16) or REAL*16

  A REAL(KIND=16) constant has more than four times the accuracy of a
  REAL number, and a greater range.

  A REAL(KIND=16) constant occupies 16 bytes of memory.  The number
  of digits that precede the exponent is unlimited, but typically
  only the leftmost 33 digits are significant.

10  –  Type of BOH Constants

  Binary, octal, and hexadecimal constants are "typeless" numeric
  constants.  They assume data types based on their usage, according
  to the following rules:

   o  When the constant is used with a binary operator, including the
      assignment operator, the data type of the constant is the data
      type of the other operand.

   o  When a specific data type is required, that type is assumed for
      the constant.

   o  When the constant is used as an actual argument, if the bit
      constant is greater than 4 bytes, INTEGER*8 is assumed;
      otherwise, INTEGER*4 is assumed.

   o  When the constant is used in any other context, an INTEGER*4
      data type is assumed (unless a compiler option indicating
      integer size specifies otherwise).

  These constants specify up to 16 bytes of data.  When the length of
  the constant is less than the length implied by the data type, the
  leftmost digits have a value of zero.

  When the length of the constant is greater than the length implied
  by the data type, the constant is truncated on the left.  An error
  results if any nonzero digits are truncated.
Close Help