VMS Help
FORTRAN, Data

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

  Each constant, variable, array, expression, or function reference
  in a Fortran statement represents typed data.  The data type of
  these items can be inherent in their constructions, implied by
  convention, or explicitly declared.  The data types available in
  Fortran are integer, REAL (REAL*4), DOUBLE PRECISION (REAL*8),
  REAL*16, COMPLEX (COMPLEX*8), DOUBLE COMPLEX (COMPLEX*16), BYTE
  (equivalent to LOGICAL*1 and INTEGER*1), logical, character, and
  Hollerith.

  Constants, variables, arrays, scalar fields, aggregate fields,
  character substrings, and expressions can be specified in many
  places in a Fortran program.  Fortran statements and expressions
  have individual restrictions governing which of these items can
  used in them and in what form.  Thus, to avoid repeatedly
  enumerating lists of the various items that can be specified with
  the various statements and expressions, the items are divided into
  four general categories:  scalar reference, scalar memory
  reference, array name reference, and aggregate reference.  The
  names of these categories are used throughout the "DEC Fortran
  Language Reference Manual" to identify what can be included in a
  particular statement or expression.

  1 - Aggregate Reference

  An aggregate reference resolves itself to a reference to a
  structured data item (a record structure or substructure).  For
  example:

  Data Declarations:

     STRUCTURE /STRA/
         INTEGER  INTFLD, INTFLDARY (10)
     END STRUCTURE
       . . .
     STRUCTURE /STRB/
         CHARACTER*20  CHARFLD
         INTEGER  INTFLD, INTFLDARY (10)
         STRUCTURE STRUCFLD
             COMPLEX  CPXFLD, CPXFLDARY (10)
         END STRUCTURE
         RECORD  /STRA/  RECFLD, RECFLDARY (10)
     END STRUCTURE
       . . .
     RECORD  /STRB/  REC, RECARY (10)

  Reference Examples:

     REC --- Is a record name.

     RECARY(1)  --- Is a record array reference.

     REC.RECFLD --- Is a reference to a substructure.

     REC.RECFLDARY(1) --- Is a reference to a substructure
                          array element.

     RECARY(1).RECFLD --- Is a reference to a substructure
                          in a record array element.

     RECARY(1).RECFLDARY(1) --- Is a reference to a substructure
                                array element in a record array.

  2 - Arrays

  An array is a group of contiguous storage locations associated with
  a single symbolic name, the array name.  The individual storage
  locations, called array elements, are referred to by a subscript
  appended to the array name.  An array can have from 1 to 7
  dimensions.  The Fortran statements that establish arrays are:
  type declaration statements, the DIMENSION statement, and the
  COMMON statement.

  The data type of an array is specified in the same way as the data
  type of a variable; either implicitly by the first letter of the
  name or explicitly by a type declaration statement.

 2.1 - Declarators

  An array declarator specifies the symbolic name that identifies an
  array within a program unit and indicates the properties of the
  array.  It has the form:

     a(d[,d]...)   a is the name of the array
                   d specifies the bounds of the array in the form:

                   [dl:]du    dl is the lower bound
                              du is the upper bound

 2.2 - Subscripts

  A subscript qualifies an array name.  A subscript is a list of
  expressions, called subscript expressions, enclosed in parentheses,
  that determine which element in the array is referred to.  The
  subscript is appended to the array name it qualifies.  A subscript
  has the form:

     (s[,s]...)     s is a subscript expression

  A one-dimensional array is stored with its first element in the
  first storage location and its last element in the last storage
  location of the sequence.  A multidimensional array is stored so
  that the leftmost subscripts vary most rapidly.

  3 - Array Name Reference

  An array name reference resolves itself to the name of an array
  with no subscripts after the array name.  For example:

  Data Declarations:

     INTEGER INT, INTARY (10)
       . . .
     STRUCTURE /STRA/
         INTEGER  INTFLD, INTFLDARY (10)
     END STRUCTURE
       . . .
     STRUCTURE /STRB/
         CHARACTER*20  CHARFLD
         INTEGER  INTFLD, INTFLDARY (10)
         STRUCTURE STRUCFLD
             COMPLEX  CPXFLD, CPXFLDARY (10)
         END STRUCTURE
         RECORD  /STRA/  RECFLD, RECFLDARY (10)
     END STRUCTURE
       . . .
     RECORD  /STRB/  REC, RECARY (10)

  Reference Examples:

     INTARY --- Is a numeric or character array.

     RECARY --- Is an array of records.

     REC.INTFLDARY --- Is a numeric or character array field of
                       a record.

     REC.RECFLDARY --- Is an array of substructures within a record.

     RECARY(1).INTFLDARY --- Is a numeric or character array field of
                             a record array element.

     RECARY(1).RECFLDARY --- Is an array of substructures within a
                             record array element.

  4 - Constants

  A constant is a fixed value.  The value of a constant can be a
  numeric value, a logical value, or a character string.  There are
  seven types of constants:  integer, real, complex, bit, logical,
  character, and Hollerith.  Bit and Hollerith constants have no data
  type; they assume a data type that conforms to the context in which
  they are used.

 4.1 - Bit

  A bit constant is a binary, octal, or hexadecimal constant.  You
  can use this type of constant wherever numeric constants are
  allowed and it assumes a numeric data type according to its
  context.

  A binary constant has the form:

    'c1c2c3...cn'B      c is a 0 or 1

  An octal constant has the form:

    'c1c2c3...cn'O      c is a digit in the range 0 - 7

  A hexadecimal constant has the form:

    'c1c2c3...cn'X      c is a digit in the range 0 - 9, or a letter
          or            in the range A - F, or a - f
    'c1c2c3...cn'Z

  Bit 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, no data type
      is assumed; however, a length of 4 bytes is always used.

   o  When the constant is used in any other context, an INTEGER*4
      data type is assumed.

  Note that on VAX systems, the following example causes a
  data-typing problem:

     I = 80 * '01000000'X

  The quantity '01000000'X is typeless and assumes the data type of
  operand 80.  The compiler treats 80 as an INTEGER*2 quantity (since
  its value is within the range -32768 to 32767), and tries to
  convert '01000000'X to INTEGER*2.  Since '01000000'X is too large
  for the INTEGER*2 type, you get an error message.

  You can avoid this problem by giving the constant an INTEGER*4 type
  in a PARAMETER statement, as follows:

     INTEGER*4 K
     PARAMETER (K = '01000000'X)

 4.2 - Character

  A character constant is a string of printable ASCII characters
  enclosed by apostrophes.  A character constant has the form:

    'c1,c2,c3...cn'       c is a printable character.

  The length of the character constant is the number of characters
  between the apostrophes, except that two consecutive apostrophes
  represent a single apostrophe.  The length of a character constant
  must be in the range 1 to 2000.

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

  Compaq Fortran supports COMPLEX*8 and COMPLEX*16 complex constants.

  A COMPLEX*8 has the form:

   (c,c)             c is an integer or REAL*4 constant

  A COMPLEX*16 has the form:

   (c,c)             c is an integer, REAL*4, or REAL*8 constant
                     (at least one of the pair must be a
                                                REAL*8 constant)

 4.4 - 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:

    nHc1c2c3...cn

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

  c  Is a printable 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.

 4.5 - 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.  It
  has the form:

    snn               s  is an optional sign
                      nn is a string of decimal digits

  The value of the integer constant must be in the range -2147483648
  to 2147483647.

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

    BYTE         Same range as LOGICAL*1 and 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)

  Integer constants in an octal form are preceded by a quotation mark
  and must use only the digits 0-7.

 4.6 - Logical

  The logical constants are .TRUE.  and .FALSE.

 4.7 - REAL_4

  A REAL*4 constant can be a basic real constant (with or without a
  decimal exponent) or an integer constant followed by a decimal
  exponent.  A basic real constant has one of these forms:

     s.nn                s is an optional sign
     snn.nn              nn is a string of decimal digits
     snn.

  A decimal exponent has the form:

     Esnn                s is an optional sign
                         nn is an integer constant

 4.8 - REAL_8

  A REAL*8 constant can be a basic real constant or an integer
  constant followed by a decimal exponent.  A decimal exponent has
  the form:

     Dsnn         s is an optional sign
                  nn is a string of decimal digits

  There are two implementations of the REAL*8 constant:  D_floating
  and G_floating.  G_floating requires the /G_FLOATING command
  qualifier.

 4.9 - REAL_16

  A REAL*16 constant can be a basic real constant or an integer
  constant followed by a decimal exponent.  A decimal exponent has
  the form:

     Qsnn              s is an optional sign
                       nn is a string of decimal digits

  5 - Expressions

  An expression represents a single value.  An expression can consist
  of a single constant, variable, record element, array element, or
  function reference; or combinations of these data items plus
  certain other elements, called operators.  Operators specify
  computations to be performed on the values of the data items and a
  single result is obtained.

  Expressions are classified as arithmetic, character, relational, or
  logical.  Arithmetic expressions produce numeric values; character
  expressions produce character values; and relational and logical
  expressions produce logical values.

  The data components of an expression must be compatible and must be
  joined by compatible operators.  Expressions are evaluated one
  operator at a time according to the rules of precedence.  The
  ranking assigned to each data type is as follows:

    Data Type                    Ranking
    ---------                    -------
    BYTE, LOGICAL*1, INTEGER*1    1 (lowest)
    LOGICAL*2                     2
    LOGICAL*4                     3
    INTEGER*2                     4
    INTEGER*4                     5
    REAL*4 (REAL)                 6
    REAL*8 (DOUBLE PRECISION)     7
    REAL*16                       8
    COMPLEX*8 (COMPLEX)           9
    COMPLEX*16 (DOUBLE COMPLEX)  10 (highest)

 5.1 - Arithmetic

  Arithmetic expressions contain numeric data such as variables,
  record elements, array elements, constants, function references,
  and arithmetic expressions enclosed in parentheses.  The expression
  evaluates to a numeric value.  The numeric operators are as
  follows:

       OPERATOR    RANK        DESCRIPTION
          **        1          exponentiation (evaluated
                                   right to left)
          *         2          multiplication
          /         2          division
          +         3          addition
          -         3          subtraction

  You can use parentheses to force an order of evaluation.

 5.2 - Character

  Character expressions consist of character elements and character
  operators.  Evaluation of a character expression yields a single
  value of character data type.  A character element can be a
  constant, variable, record element, array element, substring,
  expression (optionally enclosed in parentheses), or a function
  reference.

  A character expression has the form:

    character element[//character element]...

  The concatenation operator (//) is the only character operator.
  Concatenation is from left to right.

 5.3 - Logical

  Logical expressions can contain logical and integer data such as
  variables, record elements, array elements, constants, function
  references, expressions enclosed in parentheses, and relational
  expressions.  The expression evaluates to a logical value using the
  following operators:

       OPERATOR       PRECEDENCE
        **             First (Highest)
        *,/            Second
        +,-,//         Third
        Relational
         Operators     Fourth
        .NOT.          Fifth
        .AND.          Sixth
        .OR.           Seventh
        .XOR.          Eighth (Lowest)
        .NEQV.         Eighth
        .EQV.          Eighth

 5.4 - Relational

  Relational expressions consist of either two arithmetic or two
  character expressions separated by relational operators.  The
  expression is reduced to a logical value (true or false).

        OPERATOR      DESCRIPTION
         .LT.          Less than
         .LE.          Less than or equal to
         .EQ.          Equal to
         .NE.          Not equal to
         .GT.          Greater than
         .GE.          Greater than or equal to

  Expressions of COMPLEX data type can use only .EQ. and .NE.
  operators.

  6 - Records

  The Compaq Fortran record handling capability enables you to declare
  and operate on multi-field records.  A Compaq Fortran record is a
  named data entity, consisting of one or more fields, that you
  create in your program.  Creating a record requires both a
  structure declaration (to describe the fields in the record) and a
  RECORD statement to establish the record in memory.

 6.1 - Examples

  Structure APPOINTMENT:

     Structure /APPOINTMENT/
       RECORD /DATE/             APP_DATE
       STRUCTURE /TIME/          APP_TIME (2)
           LOGICAL*1             HOUR, MINUTE
       END STRUCTURE
       CHARACTER*20              APP_MEMO (4)
       LOGICAL*1                 APP_FLAG
     END STRUCTURE

  The following statement results in the creation of both a variable
  named NEXT_APP and a 10-element array named APP_LIST.  Both the
  variable and each element of the array have the form of the
  structure APPOINTMENT.

     RECORD /APPOINTMENT/ NEXT_APP,APP_LIST(10)

  The following examples show aggregate and scalar field references.

  Aggregate:

    NEXT_APP                ! The record NEXT_APP
    NEXT_APP.APP_TIME(1)    ! An array field of the variable
                            ! NEXT_APP
    APP_LIST(3).APP_DATE    ! A 4-byte array field in the record array
                            ! APP_LIST(3)

  Scalar:

    NEXT_APP.APP_FLAG       ! A LOGICAL field of the record
                            ! NEXT_APP

    NEXT_APP.APP_MEMO(1)(1:1)
                            ! The first character of APP_MEMO(1),
                            ! a character*20 field of the record
                            ! NEXT_APP

 6.2 - Field References

  Fields within a record can be accessed collectively or
  individually.  Record references are either qualified or
  unqualified.

  A qualified reference refers to a typed data item and can be used
  wherever an ordinary variable is allowed.  Type conversion rules
  are the same as for variables.  Its form is:

     rname[.cfname...cfname].afname

  Unqualified references refer to a record structure or substructure
  and can be used (in most cases) like arrays.

     rname[.cfname...cfname]

  rname    The name used in the RECORD statement to
           identify a record.

  cfname   A substructure field name within the record
           identified by record-name.

  afname   The name of a typed data item within a structure
           declaration.

  7 - Scalar Reference

  A scalar reference is a scalar variable, scalar record field, array
  element, constant, character substring, or expression that resolves
  into a single, typed data item.  For example:

  Data Declarations:

     INTEGER INT, INTARY (10)
       . . .
     STRUCTURE /STRA/
         INTEGER  INTFLD, INTFLDARY (10)
     END STRUCTURE
       . . .
     STRUCTURE /STRB/
         CHARACTER*20  CHARFLD
         INTEGER  INTFLD, INTFLDARY (10)
         STRUCTURE STRUCFLD
             COMPLEX  CPXFLD, CPXFLDARY (10)
         END STRUCTURE
         RECORD  /STRA/  RECFLD, RECFLDARY (10)
     END STRUCTURE
       . . .
     RECORD  /STRB/  REC, RECARY (10)

  Reference Examples:

     INT --- Is a numeric variable.

     INTARY(1)  --- Is a numeric array element.

     REC.INTFLD --- Is a numeric field.

     REC.INTFLDARY(1) --- Is a numeric element of an array field.

     CHARVAR(5:10) --- Is a substring expression of a character
                       variable.

     REC.CHARFLD(5:10) --- Is a substring expression of a character
                           field.

  Note:  A scalar memory reference is the same as a scalar reference,
  excluding constants and expressions.

  8 - Substrings

  A character substring is a contiguous segment of a character
  variable, character array element, or character field reference.
  It has one of the following forms:

     v([e1]:[e2])  OR  a(s[,s]...)([e1]:[e2])

  v   Is a character variable name.

  a   Is a character array name.

  s   Is a subscript expression.

  e1  Is a numeric expression specifying the leftmost
      character position of the substring.

  e2  Is a numeric expression specifying the rightmost
      character position of the substring.

  NOTE:
    1 .LE. e1 .LE. e2 .LE. length-of-v must hold true

  9 - Types

  The Fortran data types are as follows:

     o Integer - A whole number

     o REAL (REAL*4) - A single-precision floating-point number
                       (a whole number or a decimal fraction or
                       a combination)

     o DOUBLE PRECISION (REAL*8) - A double-precision floating-point
                       number (like REAL*4, but with twice the
                       degree of accuracy in its representation)

     o REAL*16 - A quad-precision floating-point number (like REAL*4,
                 but with four times the degree of accuracy in its
                 representation.)

     o COMPLEX (COMPLEX*8)  -  A pair of REAL*4 values representing
                 a complex number (the first part of the number is
                 the real part, the second is the imaginary part)

     o COMPLEX*16 (DOUBLE COMPLEX)  -  Similar to complex, but with
                 twice the degree of accuracy in its representation
                 (its real or imaginary part must be a REAL*8)

     o Logical - A logical value, .TRUE. or .FALSE.

     o Character - A sequence of characters

 9.1 - Character

  A character string is a contiguous sequence of bytes in memory.  A
  character string is specified by two attributes:  the address of
  the first byte of the string and the length of the string in bytes.
  The length of the string must be in the range 1 through 65535.

  Hollerith constants are stored internally, one character per byte.

 9.2 - COMPLEX

  Real and complex numbers are floating-point representations.

  COMPLEX*8 (F_floating) data is eight contiguous bytes aligned on an
  arbitrary byte boundary.  The low-order four bytes contain REAL*4
  data that represents the real part of the complex number.  The
  high-order four bytes contain REAL*4 data that represents the
  imaginary part of the complex number.

  COMPLEX*16 (D_floating) data is 16 contiguous bytes aligned on an
  arbitrary byte boundary.  The low-order bytes contain REAL*8
  (D_floating) data that represents the real part of the complex
  data.  The high-order eight bytes contain REAL*8 (D_floating) data
  that represents the imaginary part of the complex data.

  COMPLEX*16 (G_floating) data is 16 contiguous bytes aligned on an
  arbitrary byte boundary.  The low-order bytes contain REAL*8
  (G_floating) data that represents the real part of the complex
  data.  The high-order eight bytes contain REAL*8 (G_floating) data
  that represents the imaginary part of the complex data.

 9.3 - Integer

  Integer values are stored in two's complement form; INTEGER*2 uses
  two contiguous bytes and must be in the range -32768 to 32767.
  INTEGER*4 uses four contiguous bytes and must be in the range
  -2147483648 to 2147483647.  If the value is in the range of an
  INTEGER*2, then the first word can be referenced as an INTEGER*2
  value.

 9.4 - Logical

  Logical values start on an arbitrary byte boundary and are stored
  in one, two, or four contiguous bytes.  The low-order bit (bit 0)
  determines the value.  If bit 0 is set, the value is .TRUE.; if bit
  0 is clear, the value is .FALSE.  The remaining bits are undefined.

 9.5 - REAL

  Real and complex numbers are floating-point representations.

  The exponent for REAL*4 and REAL*8 (D_floating) formats is stored
  in binary excess 128 notation.  Binary exponents from -127 to 127
  are represented by the binary equivalents of 1 through 255.

  The exponent for the REAL*8 (G_floating) format is stored in binary
  excess 1024 notation.  The exponent for the REAL*16 format is
  stored in binary excess 16384 notation.  In REAL*8 (G_floating)
  format, binary exponent from -1023 to 1023 are represented by the
  binary equivalents of 1 through 2047.  In REAL*16 format, binary
  exponents from -16383 to 16383 are represented by the binary
  equivalents of 1 through 32767.

  For each floating-point format, fractions are represented in
  sign-magnitude notation, with the binary radix point to the left of
  the most significant bit.  Fractions are assumed to be normalized,
  and therefore the most significant bit is not stored.  This bit is
  assumed to be 1 unless the exponent is 0., in which case the value
  represented is either zero or is a reserved operand.

  REAL*4 (F_floating) numbers occupy four contiguous bytes and the
  precision is approximately one part in 2**23, that is, typically 7
  decimal digits.

  REAL*8 (D_floating) numbers occupy eight contiguous bytes and the
  precision is approximately one part in 2**55, that is, typically 16
  decimal digits.

  REAL*8 (G_floating) numbers occupy eight contiguous bytes the
  precision is approximately one part in 2**52, that is, typically 15
  decimal digits.

  REAL*16 (H_floating) numbers occupy sixteen contiguous bytes and
  the precision is approximately 2**112, that is, typically 33
  decimal digits.

  10 - Variables

  A variable is represented by a symbolic name that is associated
  with a storage location.  The value of the variable is the value
  currently stored in that location; the value can be changed by
  assigning a new value to the variable.

  Variables, like constants, are classified by data type.  When data
  of any type is assigned to a variable, it is converted, if
  necessary, to the data type of the variable.  You can establish the
  data type of a variable by type declaration statements, IMPLICIT
  statements, or predefined typing rules.

 10.1 - Implication

  In the absence of either IMPLICIT statements or explicit type
  statements, all variables with names beginning with I, J, K, L, M,
  or N are assumed to be integer variables.  Variables beginning with
  any other letter are assumed to be REAL*4 variables.

 10.2 - Specification

  Type declaration statements explicitly define the data type of
  variables.

  Numeric type declaration statements have the form:

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

  type   Is any data type except CHARACTER.

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

  clist  Is a list of constants.

  Character type declaration statements have the form:

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

  len    Is an unsigned integer constant, an integer constant
         expression enclosed in parentheses, or an asterisk
         enclosed in parentheses.

         The value of len specifies the length of the character
         data elements.

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

         The name can optionally be followed by a data type
         length specifier (*n).  For character entities, the length
         specifier can be *len or *(*).

  clist  Is an initial value or values to be assigned to the
         immediately preceding variable or array element.
  Close     HLB-list     TLB-list     Help  

[legal] [privacy] [GNU] [policy] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.