VMS Help  —  FORTRAN  Data
CHARACTER(LEN=20) ITEM_NAME END TYPE ITEM TYPE PRODUCE REAL MARKUP TYPE(ITEM) FRUIT END TYPE PRODUCE In this case, you must use an embedded structure constructor to specify the values of that component; for example: PRODUCE(.70, ITEM (.25, "Daniels", "apple"))

4  –  Expressions

  An expression represents either a data reference or a computation,
  and is formed from operators, operands, and parentheses.  The
  result of an expression is either a scalar value or an array of
  scalar values.

  If the value of an expression is of intrinsic type, it has a kind
  type parameter.  (If the value is of intrinsic type CHARACTER, it
  also has a length parameter.) If the value of an expression is of
  derived type, it has no kind type parameter.

  An operand is a scalar or array.  An operator can be either
  intrinsic or defined.  An intrinsic operator is known to the
  compiler and is always available to any program unit.  A defined
  operator is described explicitly by a user in a function subprogram
  and is available to each program unit that uses the subprogram.

  The simplest form of an expression (a primary) can be any of the
  following:

   o  A constant; for example, 4.2

   o  A subobject of a constant; for example, 'LMNOP'(2:4)

   o  A variable; for example, VAR1

   o  A structure constructor; for example, EMPLOYEE(3472, "JOHN
      DOE")

   o  An array constructor; for example, (/12.0,16.0/)

   o  A function reference; for example, COS(X)

   o  Another expression in parentheses; for example, (I+5)

  Any variable or function reference used as an operand in an
  expression must be defined at the time the reference is executed.
  If the operand is a pointer, it must be associated with a target
  object that is defined.  An integer operand must be defined with an
  integer value rather than a statement label value.  All of the
  characters in a character data object reference must be defined.

  When a reference to an array or an array section is made, all of
  the selected elements must be defined.  When a structure is
  referenced, all of the components must be defined.

  In an expression that has intrinsic operators with an array as an
  operand, the operation is performed on each element of the array.
  In expressions with more than one array operand, the arrays must be
  conformable (they must have the same shape).  The operation is
  applied to corresponding elements of the arrays, and the result is
  an array of the same shape (the same rank and extents) as the
  operands.

  In an expression that has intrinsic operators with a pointer as an
  operand, the operation is performed on the value of the target
  associated with the pointer.

  For defined operators, operations on arrays and pointers are
  determined by the procedure defining the operation.

  A scalar is conformable with any array.  If one operand of an
  expression is an array and another operand is a scalar, it is as if
  the value of the scalar were replicated to form an array of the
  same shape as the array operand.  The result is an array of the
  same shape as the array operand.

  The ranking assigned to each numeric intrinsic data type follows:

    Data Type                    Ranking
    ---------                    -------
    LOGICAL*1 and BYTE            lowest
    LOGICAL*2                       .
    LOGICAL*4                       .
    LOGICAL*8                       .
    INTEGER*1                       .
    INTEGER*2                       .
    INTEGER*4                       .
    INTEGER*8                       .
    REAL (REAL*4)                   .
    REAL*16                         .
    DOUBLE PRECISION (REAL*8)       .
    COMPLEX (COMPLEX*8)             .
    DOUBLE COMPLEX (COMPLEX*16)     .
    COMPLEX*32                   highest

4.1  –  Numeric

  Numeric (arithmetic) expressions are formed with numeric operands
  and numeric operators, and yield a single numeric value.

  The term numeric includes logical data, because logical data is
  treated as integer data when used in a numeric context.  (.TRUE.
  is -1; .FALSE.  is 0.)

  The numeric operators are as follows:

       Operator    Description
       -----------------------
          **       exponentiation (evaluated
                            right to left)
          *        multiplication
          /        division
          +        addition
          -        subtraction

  You can use parentheses to force an order of evaluation.

4.2  –  Character

  Character expressions consist of character items and character
  operators.  Evaluation of a character expression yields a single
  value of character data type.

  A character expression has the form:

    character operand[//character operand]...

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

4.3  –  Defined Operations

  A defined operation is unary or binary.  It is defined by a
  function subprogram containing a generic interface block with the
  specifier OPERATOR.  A defined operation is not an intrinsic
  operation.  However, you can use a defined operation to extend the
  meaning of an intrinsic operator.

  For defined unary operations, the function must contain one
  argument.  For defined binary operations, the function must contain
  two arguments.

  Interpretation of the operation is provided by the function that
  defines the operation.

  A Fortran 95/90 defined operator can contain up to 31 letters, and
  is enclosed in periods (.).  Its name cannot be the same name as
  any of the following:

    o The intrinsic operators  .NOT., .AND., .OR., .XOR.,
      .EQV., .NEQV., .EQ., .NE., .GT., .GE., .LT., and .LE.

    o The logical literal constants .TRUE. or .FALSE..

  No two intrinsic operators can follow one another, but an intrinsic
  or binary operator can be followed by a defined unary operator.

  The result of a defined operation can have any type.  The type of
  the result (and its value) must be specified by the defining
  function.

  The following examples show expressions containing defined
  operators:

    .COMPLEMENT. A

    X .PLUS. Y .PLUS. Z

    M * .MINUS. N

4.4  –  Initialization

  An initialization expression must evaluate at compile time to a
  constant.  It is used to specify an initial value for an entity.

  In an initialization expression, each operation is intrinsic and
  each operand is one of the following:

   o  A constant or subobject of a constant

   o  An array constructor where each element, and the bounds and
      strides of each implied-do are expressions whose primaries are
      initialization expressions

   o  A structure constructor whose components are initialization
      expressions

   o  An elemental intrinsic function reference of type integer or
      character, whose arguments are initialization expressions of
      type integer or character

   o  A reference to one of the following inquiry functions:

          BIT_SIZE      MINEXPONENT
          DIGITS        PRECISION
          EPSILON       RADIX
          HUGE          RANGE
          ILEN          SHAPE
          KIND          SIZE
          LBOUND        TINY
          LEN           UBOUND
          MAXEXPONENT

      Each function argument must be one of the following:

          - An initialization expression
          - A variable whose kind type parameter and bounds
              are not assumed or defined by an ALLOCATE statement,
              pointer assignment, or an expression that is not an
              initialization expression

   o  A reference to one of the following transformational functions
      (each argument must be an initialization expression):

          REPEAT
          RESHAPE
          SELECTED_INT_KIND
          SELECTED_REAL_KIND
          TRANSFER
          TRIM

   o  A reference to the transformational function NULL

   o  An implied-do variable within an array constructor where the
      bounds and strides of the corresponding implied-do are
      initialization expressions

   o  Another initialization expression enclosed in parentheses

  Each subscript, section subscript, and substring starting and
  ending point must be an initialization expression.

  In an initialization expression, the exponential operator (**) must
  have a power of type integer.

  If an initialization expression invokes an inquiry function for a
  type parameter or an array bound of an object, the type parameter
  or array bound must be specified in a prior specification statement
  (or to the left of the inquiry function in the same statement).

4.5  –  Logical

  Logical expressions can contain one or more logical operators and
  logical, integer, or relational operands.  The following are
  logical operators:

     Operator  Meaning
     ---------------------------
     .AND.     Logical conjunction: the expression A .AND. B
               is true if both A and B are true.

     .OR.      Logical disjunction (inclusive OR):  the ex-
               pression A .OR. B is true if either A, B, or
               both, are true.

     .XOR.     Same as .NEQV.

     .NEQV.    Logical inequivalence (or exclusive OR): the
               expression A .NEQV. B is true if either A or
               B is true, but false if both are true.

     .EQV.     Logical equivalence: the expression A .EQV. B
               is true if both A and B are true, or both are
               false.

     .NOT.     Logical negation: the expression .NOT. A is
               true if A is false and false if A is true.

4.6  –  Operator Precedence

  The following shows the precedence of all intrinsic and defined
  operators:

  Category    Operator                     Precedence
  ---------------------------------------------------
  N/A         Defined Unary Operators      Highest
  Numeric     **                              .
  Numeric     * or /                          .
  Numeric     Unary + or -                    .
  Numeric     Binary + or -                   .
  Character   //                              .
  Relational  .EQ.,.NE.,.LT.,.LE.,.GT.,.GE.   .
  Logical     .NOT.                           .
  Logical     .AND.                           .
  Logical     .OR.                            .
  Logical     .XOR., .EQV., .NEQV.            .
  N/A         Defined Binary Operators     Lowest

4.7  –  Relational

  Relational expressions consist of two or more expressions whose
  values are compared to determine whether the relationship stated by
  the relational operator is satisfied.  The expression is reduced to
  a logical value (true or false).

  The following are relational operators:

        Operator         Meaning
        ------------------------------------------
         .LT. or <       Less than
         .LE. or <=      Less than or equal to
         .EQ. or ==      Equal to
         .NE. or /=      Not equal to
         .GT. or >       Greater than
         .GE. or >=      Greater than or equal to

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

4.8  –  Specification

  A specification expression is a restricted expression that is of
  type integer and has a scalar value.  This type of expression
  appears only in the declaration of array bounds and character
  lengths.

  In a restricted expression, each operation is intrinsic and each
  operand is one of the following:

   o  A constant or subobject of a constant

   o  A variable that is one of the following:

          - A dummy argument that does not have the OPTIONAL or
              INTENT (OUT) attribute (or the subobject of such
              a variable)
          - In a common block (or the subobject of such a variable)
          - Made accessible by use or host association (or the
              subobject of such a variable)

   o  A structure constructor whose components are restricted
      expressions

   o  An implied-do variable within an array constructor where the
      bounds and strides of the corresponding implied-do are
      initialization expressions

   o  A reference to one of the following inquiry functions:

          BIT_SIZE               NWORKERS
          DIGITS                 PRECISION
          EPSILON                PROCESSORS_SHAPE
          HUGE                   RADIX
          ILEN                   RANGE
          KIND                   SHAPE
          LBOUND                 SIZE
          LEN                    SIZEOF
          MAXEXPONENT            TINY
          MINEXPONENT            UBOUND
          NUMBER_OF_PROCESSORS

      Each function argument must be one of the following:

          - A restricted expression
          - A variable whose properties inquired about are not
            dependent on the upper bound of the last dimension
            of an assumed-size array, are not defined by an
            expression that is a restricted expression, or are
            not definable by an ALLOCATE or pointer assignment
            statement.

   o  A reference to any other intrinsic function where each argument
      is a restricted expression.

   o  A reference to a specification function (see below) where each
      argument is a restricted expression

   o  An array constructor where each element, and bounds and strides
      of each implied-do are expressions whose primaries are
      restricted expressions

   o  Another restricted expression enclosed in parentheses

  Each subscript, section subscript, and substring starting and
  ending point must be a restricted expression.

  Specification functions can be used in specification expressions to
  indicate the attributes of data objects.  A specification function
  is a pure function.  It cannot have a dummy procedure argument or
  be any of the following:

   o  An intrinsic function

   o  An internal function

   o  A statement function

   o  Defined as RECURSIVE

  A variable in a specification expression must have its type and
  type parameters (if any) specified in one of the following ways:

   o  By a previous declaration in the same scoping unit

   o  By the implicit typing rules currently in effect for the
      scoping unit

   o  By host or use association

  If a variable in a specification expression is typed by the
  implicit typing rules, its appearance in any subsequent type
  declaration statement must confirm the implied type and type
  parameters.

  If a specification expression invokes an inquiry function for a
  type parameter or an array bound of an object, the type parameter
  or array bound must be specified in a prior specification statement
  (or to the left of the inquiry function in the same statement).

5  –  Intrinsic Types

  VSI Fortran provides the following intrinsic data types:

   o  INTEGER (4 kind type parameters) - a whole number

   o  REAL (3 kind type parameters) - a floating point number (a
      whole number, a decimal fraction, or a combination)

   o  DOUBLE PRECISION - a REAL kind type parameter that has more
      than twice the degree of accuracy in its representation, and
      greater range

   o  COMPLEX (3 kind type parameters) - a pair of REAL values
      representing a complex number (the first part of the number is
      the real part, the second is the imaginary part)

   o  DOUBLE COMPLEX - a COMPLEX kind type parameter with DOUBLE
      PRECISION real and imaginary parts

   o  LOGICAL (4 kind type parameters)- a logical value, .TRUE.  or
      .FALSE.

   o  CHARACTER - a sequence of characters

   o  BYTE - a one-byte value equivalent to INTEGER(KIND=1)

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

5.2  –  COMPLEX

  Real and complex numbers are floating-point representations.

  COMPLEX(KIND=4) (or COMPLEX*8) data is eight contiguous bytes
  aligned on an arbitrary byte boundary.  The low-order four bytes
  contain REAL(KIND=4) (or REAL*4) data that represents the real part
  of the complex number.  The high-order four bytes contain REAL data
  that represents the imaginary part of the complex number.  For
  information on the ranges of REAL data, see REAL (within the DATA
  CONSTANTS section of online Help).

  DOUBLE COMPLEX (COMPLEX(KIND=8) or COMPLEX*16) data is 16
  contiguous bytes aligned on an arbitrary byte boundary.  The
  low-order bytes contain DOUBLE PRECISION data that represents the
  real part of the complex number.  The high-order eight bytes
  contain DOUBLE PRECISION data that represents the imaginary part of
  the complex data.  For information on the ranges of DOUBLE
  PRECISION data, see DOUBLE_PRECISION (within the DATA CONSTANTS
  section of online Help).

  COMPLEX(KIND=16) (or COMPLEX*32) data is 32 contiguous bytes
  aligned on an arbitrary byte boundary.  The low-order bytes contain
  REAL(KIND=16) (or REAL*16) data that represents the real part of
  the complex number.  The high-order bytes contain REAL*16 data that
  represents the imaginary part of the complex number.  For
  information on the ranges of REAL*16 data, see REAL (within the
  DATA CONSTANTS section of online Help).

5.3  –  INTEGER

  Integer numbers are whole numbers.  For information on the ranges
  of INTEGER data, see INTEGER (within the DATA CONSTANTS section of
  online Help).

  INTEGER*2, INTEGER*4, and INTEGER*8 values are stored in two's
  complement form.

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

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

  When a logical value is stored in memory, all of its bits are
  stored.  For example, consider the following:

     LOGICAL*4 L1, L2, L3
     L1 = L2 .AND. L3

  This example does a full 32-bit AND of L2 and L3, and stores all 32
  resulting bits in L1.

5.5  –  REAL

  Real and complex numbers are floating-point representations.

  The exponent for REAL(KIND=4) (or REAL*4) (F_floating) and DOUBLE
  PRECISION (REAL(KIND=8) or 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 DOUBLE PRECISION G_floating format and
  T_floating format is stored in binary excess 1024 notation.  The
  exponent for the REAL*16 format is stored in binary excess 16384
  notation.  In DOUBLE PRECISION (G_floating) format, binary exponents
  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 floating-point format, fractions are represented in
  sign-magnitude notation, with the binary radix point to the left of
  the most significant bit for F_floating, D_floating, and G_floating,
  and to the right of the most significant bit for S_floating and
  T_floating.  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(KIND=4) (or REAL*4) numbers occupy four contiguous bytes and
  the precision is approximately one part in 2**23, that is,
  typically 7 decimal digits.

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

  DOUBLE PRECISION G_floating numbers occupy eight contiguous bytes
  and 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.

  For more information on real data type ranges, see DATA CONSTANTS
  REAL and DATA CONSTANTS DOUBLE_PRECISION in this Help file.

6  –  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])
     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

  Both e1 and e2 must be within the range 1,2, ..., len, where len is
  the length of the parent character string.  If e1 exceeds e2, the
  substring has length zero.

7  –  Variables

  A variable is a data object whose value can be changed at any point
  in a program.  It can be any of the following:

   o  A scalar name

      A scalar is a single object that has a single value; it can be
      of any intrinsic or user-defined type.

   o  An array name

      An array is a collection of scalar elements of any intrinsic or
      derived type.  All elements must be have the same type and kind
      type parameter.

   o  A subobject designator

      A subobject is part of an object.  The following are
      subobjects:

        An array element
        An array section
        A structure component
        A substring

      For example, B(3) is a subobject (array element) designator for
      array B.  A subobject cannot be a variable if its parent object
      is a constant.

  The name of a variable is associated with a single storage
  location.

  Variables are classified by data type, as constants are.  The data
  type of a variable indicates the type of data it contains,
  including its precision, and implies its storage requirements.
  When data of any type is assigned to a variable, it is converted to
  the data type of the variable (if necessary).

  A variable is usually defined in a type declaration statement or
  DATA statement.  But during program execution, events can occur to
  cause variables to be defined or redefined (such as assignment
  statements and READ statements), or undefined (such as an I/O
  error).

  Scalar variables are assigned data types explicitly in type
  declaration statements or IMPLICIT statements, or they can have
  implicit data types.

7.1  –  Implicit Typing

  By default, 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 variables.

  Names beginning with a dollar sign ($) are implicitly INTEGER.

  You can override the default data type implied in a name by
  specifying data type explicitly in either an IMPLICIT statement or
  a type declaration statement.

  Note:  You cannot change the implicit type of a name beginning with
  a dollar sign in an IMPLICIT statement.

7.2  –  Explicit Typing

  Type declaration statements explicitly specify the data type of
  scalar variables.  For example, the following statements associate
  VAR1 with an 8-byte complex storage location, and VAR2 with an
  8-byte double-precision storage location:

    COMPLEX VAR1
    DOUBLE PRECISION VAR2

  You can explicitly specify the data type of a scalar variable only
  once.

  An explicit data type specification takes precedence over the type
  specified by an IMPLICIT statement.  If no explicit data type
  specification appears, any variable with a name that begins with
  the letter in the range specified in the IMPLICIT statement becomes
  the data type of the variable.

  Character type declaration statements specify that given variables
  represent character values with the length specified.  For example,
  the following statements associate the variable names INLINE, NAME,
  and NUMBER with storage locations containing character data of
  lengths 72, 12, and 9, respectively:

    CHARACTER*72 INLINE
    CHARACTER NAME*12, NUMBER*9

  In single subprograms, assumed-length character arguments can be
  used to process character strings with different lengths.  The
  assumed-length character argument has its length specified with an
  asterisk, for example:

    CHARACTER*(*) CHARDUMMY

  The argument CHARDUMMY assumes the length of the actual argument.
Close Help