HELPLIB.HLB  —  FORTRAN  Data
  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.

  Each data type has a name, a set of associated values, a way to
  denote the values, and operations to manipulate and interpret these
  values.

  There are two categories of data types:  intrinsic and derived.
  The names of the intrinsic data types are predefined and are always
  accessible.  Derived data types are user-defined data types that
  are made up of intrinsic or derived data types.

1  –  Arrays

  An array is a set of scalar elements that have the same type and
  kind type parameters.  Any object that is declared with an array
  specification is an array.  Arrays can be declared with a type
  declaration statement, a DIMENSION statement, or a COMMON
  statement.

  An array can be referenced by element (using subscripts), by
  section (using a section subscript list), or as a whole.

  A section subscript list consists of subscripts, subscript
  triplets, or vector subscripts.  At least one subscript in the list
  must be a subscript triplet or vector subscript.

  When an array name without any subscripts appears in an intrinsic
  operation (for example, addition), the operation applies to the
  whole array (all elements in the array).

  An array has the following properties:

   o  Data type

      An array can have any intrinsic or derived type.  The data type
      of an array is either specified in a type declaration
      statement, or implied by the first letter of its name.  All
      elements of the array have the same type and kind type
      parameters.  If a value assigned to an individual array element
      is not the same as the type of the array, it is converted to
      the array's type.

   o  Rank

      The rank of an array is the number of dimensions in the array.
      An array can have up to seven dimensions.  A rank-one array
      represents a column of data (a vector), a rank-two array
      represents a table of data arranged in columns and rows (a
      matrix), a rank-three array represents a table of data on
      multiple pages (or planes), and so forth.

   o  Bounds

      Arrays have a lower and upper bound in each dimension.  These
      bounds determine the range of values that can be used as
      subscripts for the dimension.  The value of either bound can be
      positive, negative, or zero.

      The bounds of a dimension are defined in an array
      specification.

   o  Size

      The size of an array is the total number of elements in the
      array (the product of the array's extents).

      The extent of a dimension is the number of elements in that
      dimension.  It is determined as follows:  upper bound - lower
      bound + 1.  If the value of any of an array's extents is zero,
      the array has a size of zero.

   o  Shape

      The shape of an array is determined by its rank and extents,
      and can be represented as a rank-one array (vector) where each
      element is the extent of the corresponding dimension.

      Two arrays with the same shape are said to be conformable.  A
      scalar is conformable to an array of any shape.

  The name and rank of an array are constant and must be specified
  when the array is declared.  The extent of each dimension can be
  constant, but does not need to be.  The extents can vary during
  program execution if the array is a dummy argument array, an
  automatic array, an array pointer, or an allocatable array.

  A whole array is referenced by the array name.  Individual elements
  in a named array are referenced by a scalar subscript or list of
  scalar subscripts (if there is more than one dimension).  A section
  of a named array is referenced by a section subscript.

  Consider the following array declaration:

    INTEGER L(2:11,3)

  The properties of array L are as follows:

    Data type:   INTEGER
    Rank:        2 (two dimensions)
    Bounds:      First dimension: 2 to 11
                 Second dimension: 1 to 3
    Size:        30 (the product of the extents: 10 x 3)
    Shape:       10 by 3 (a vector of the extents (10,3))

  The following example shows other valid ways to declare this array:

    DIMENSION L(2:11,3)
    INTEGER, DIMENSION(2:11,3) :: L
    COMMON L(2:11,3)

  The following example shows references to array elements, array
  sections, and a whole array:

    REAL B(10)      ! Declares a rank-one array with 10 elements

    INTEGER C(5,8)  ! Declares a rank-two array with 5 elements
                    !   in dimension one and 8 elements in
                    !   dimension two
    ...
    B(3) = 5.0      ! Reference to an array element
    B(2:5) = 1.0    ! Reference to an array section consisting of
                    !   elements: B(2), B(3), B(4), B(5)
    ...
    C(4,8) = I      ! Reference to an array element
    C(1:3,3:4) = J  ! Reference to an array section consisting of
                    !   elements:  C(1,3) C(1,4)
                    !              C(2,3) C(2,4)
                    !              C(3,3) C(3,4)
    B = 99          ! Reference to a whole array consisting of
                    !   elements: B(1), B(2), B(3), B(4), B(5),
                    !   B(6), B(7), B(8), B(9), and B(10)

1.1  –  Declarators

  An array specification (or array declarator) declares the shape of
  an array.  It takes the following form:

    (array-spec)

    array-spec   Is one of the following array specifications:

                 Explicit-shape
                 Assumed-shape
                 Assumed-size
                 Deferred-shape

  The array specification is appended to the name of the array when
  the array is declared.

  The following examples show different forms of array
  specifications:

  SUBROUTINE SUB(N, C, D, Z)
    REAL, DIMENSION(N, 15) :: IARRY  ! An explicit-shape array
    REAL C(:), D(0:)                 ! An assumed-shape array
    REAL, POINTER :: B(:,:)          ! A deferred-shape array pointer
    REAL :: Z(N,*)                   ! An assumed-size array

    REAL, ALLOCATABLE, DIMENSION(:) :: K  ! A deferred-shape
                                          !    allocatable array

1.1.1  –  Explicit Shape

  An explicit-shape array is declared with explicit values for the
  bounds in each dimension of the array.  An explicit-shape
  specification takes the following form:

     [lower-bound:] upper-bound [,[lower-bound:] upper-bound ]...

  The lower bound (if present) and the upper bound are specification
  expressions that have a positive, negative, or zero value.  If
  necessary, the bound value is converted to integer type.

  If the lower bound is not specified, it is assumed to be 1.

  The bounds can be specified as constant or nonconstant expressions,
  as follows:

   o  If the bounds are constant expressions, the subscript range of
      the array in a dimension is the set of integer values between
      and including the lower and upper bounds.  If the lower bound
      is greater than the upper bound, the range is empty, the extent
      in that dimension is zero, and the array has a size of zero.

   o  If the bounds are nonconstant expressions, the array must be
      declared in a procedure.  The bounds can have different values
      each time the procedure is executed, since they are determined
      when the procedure is entered.

      The bounds are not affected by any redefinition or undefinition
      of the specification variables that occurs while the procedure
      is executing.

      The following explicit-shape arrays can specify nonconstant
      bounds:

         - An automatic array (the array is a local
              variable)
         - An adjustable array (the array is a dummy
              argument to a subprogram)

  The following are examples of explicit-shape specifications:

    INTEGER I(3:8, -2:5) ! Rank-two array; range of dimension one is
    ...                  !  3 to 8, range of dimension two is -2 to 5
    SUBROUTINE SUB(A, B, C)
      INTEGER :: B, C
      REAL, DIMENSION(B:C) :: A  ! Rank-one array; range is B to C

1.1.1.1  –  Automatic Arrays

  An automatic array is an explicit-shape array that is a local
  variable.  Automatic arrays are only allowed in function and
  subroutine subprograms, and are declared in the specification part
  of the subprogram.  At least one bound of an automatic array must
  be a nonconstant specification expression.  The bounds are
  determined when the subprogram is called.

  The following example shows automatic arrays:

    SUBROUTINE SUB1 (A, B)
      INTEGER A, B, LOWER
      COMMON /BOUND/ LOWER
      ...
      INTEGER AUTO_ARRAY1(B)
      ...
      INTEGER AUTO_ARRAY2(LOWER:B)
      ...
      INTEGER AUTO_ARRAY3(20, B*A/2)
    END SUBROUTINE

1.1.1.2  –  Adjustable Arrays

  An adjustable array is an explicit-shape array that is a dummy
  argument to a subprogram.  At least one bound of an adjustable
  array must be a nonconstant specification expression.  The bounds
  are determined when the subprogram is called.

  The array specification can contain integer variables that are
  either dummy arguments or variables in a common block.

  When the subprogram is entered, each dummy argument specified in
  the bounds must be associated with an actual argument.  If the
  specification includes a variable in a common block, it must have a
  defined value.  The array specification is evaluated using the
  values of the actual arguments, as well as any constants or common
  block variables that appear in the specification.

  The size of the adjustable array must be less than or equal to the
  size of the array that is its corresponding actual argument.

  To avoid possible errors in subscript evaluation, make sure that
  the bounds expressions used to declare multidimensional adjustable
  arrays match the bounds as declared by the caller.

  In the following example, the function computes the sum of the
  elements of a rank-two array.  Notice how the dummy arguments M and
  N control the iteration:

      FUNCTION MY_SUM(A, M, N)
        DIMENSION A(M, N)
        SUMX = 0.0
        DO J = 1, N
          DO I = 1, M
            SUMX = SUMX + A(I, J)
          END DO
        END DO
        MY_SUM = SUMX
      END FUNCTION

  The following are examples of calls on SUM:

    DIMENSION A1(10,35), A2(3,56)
    SUM1 = MY_SUM(A1,10,35)
    SUM2 = MY_SUM(A2,3,56)

1.1.2  –  Assumed Shape

  An assumed-shape array is a dummy argument array that assumes the
  shape of its associated actual argument array.  An assumed-shape
  specification takes the following form:

     [lower-bound]: [,[lower-bound]:] ...

  The lower bound is a specification expression.  If the lower bound
  is not specified, it is assumed to be 1.

  The rank of the array is the number of colons (:) specified.

  The value of the upper bound is the extent of the corresponding
  dimension of the associated actual argument array + lower-bound -
  1.

  The following is an example of an assumed-shape specification:

    INTERFACE
      SUBROUTINE SUB(M)
        INTEGER M(:, 1:, 5:)
      END SUBROUTINE
    END INTERFACE
    INTEGER L(20, 5:25, 10)
    CALL SUB(L)

    SUBROUTINE SUB(M)
      INTEGER M(:, 1:, 5:)
    END SUBROUTINE

  Array M has the same extents as array L, but array M has bounds
  (1:20, 1:21, 5:14).

  Note that an explicit interface is required when calling a routine
  that expects an assumed-shape or pointer array.

1.1.3  –  Assumed Size

  An assumed-size array is a dummy argument array that assumes the
  size (only) of its associated actual argument array; the rank and
  extents can differ for the actual and dummy arrays.  An
  assumed-size specification takes the following form:

     [exp-shape-spec,] [exp-shape-spec,]... [lower-bound:] *

  The exp-shape-spec is an explicit-shape specification (see DATA
  ARRAY DECL EXPL in online Help).

  The lower bound and upper bound are specification expressions that
  have a positive, negative, or zero value.  If necessary, the bound
  value is converted to integer type.  If a lower bound is not
  specified, it is assumed to be 1.

  The asterisk (*) represents the upper bound of the last dimension.

  The rank of the array is the number of explicit-shape
  specifications plus 1.

  The size of the array is assumed from the actual argument
  associated with the assumed-size dummy array as follows:

   o  If the actual argument is an array of type other than default
      character, the size of the dummy array is the size of the
      actual array.

   o  If the actual argument is an array element of type other than
      default character, the size of the dummy array is a + 1 - s,
      where "s" is the subscript value and "a" is the size of the
      actual array.

   o  If the actual argument is a default character array, array
      element, or array element substring, and it begins at character
      storage unit b of an array with n character storage units, the
      size of the dummy array is as follows:

        MAX(INT((n + 1 - b) / y), 0)

      The "y" is the length of an element of the dummy array.

  An assumed-size array can only be used as a whole array reference
  in the following cases:

   o  When it is an actual argument in a procedure reference that
      does not require the shape

   o  In the intrinsic function LBOUND

  Because the actual size of an assumed-size array is unknown, an
  assumed-size array cannot be used as any of the following in an I/O
  statement:

   o  An array name in the I/O list

   o  A unit identifier for an internal file

   o  A run-time format specifier

  The following is an example of an assumed-size specification:

    SUBROUTINE SUB(A, N)
      REAL A, N
      DIMENSION A(1:N, *)
      ...

1.1.4  –  Deferred Shape

  A deferred-shape array is an array pointer or an allocatable array.

  The array specification contains a colon (:) for each dimension of
  the array.  No bounds are specified.  The bounds (and shape) of
  allocatable arrays and array pointers are determined when space is
  allocated for the array during program execution.

  An array pointer is an array declared with the POINTER attribute.
  Its bounds and shape are determined when it is associated with a
  target by pointer assignment, or when the pointer is allocated by
  execution of an ALLOCATE statement.

  In pointer assignment, the lower bound of each dimension of the
  array pointer is the result of the LBOUND intrinsic function
  applied to the corresponding dimension of the target.  The upper
  bound of each dimension is the result of the UBOUND intrinsic
  function applied to the corresponding dimension of the target.

  A pointer dummy argument can be associated only with a pointer
  actual argument.  An actual argument that is a pointer can be
  associated with a nonpointer dummy argument.

  A function result can be declared to have the pointer attribute.

  An allocatable array is declared with the ALLOCATABLE attribute.
  Its bounds and shape are determined when the array is allocated by
  execution of an ALLOCATE statement.

  The following are examples of deferred-shape specifications:

    REAL, ALLOCATABLE :: A(:,:)       ! Allocatable array
    REAL, POINTER :: C(:), D (:,:,:)  ! Array pointers

1.2  –  Whole Arrays

  A whole array is referenced by the name of the array (without any
  subscripts).  It can be a named constant or a variable.

  If a whole array appears in a nonexecutable statement, the
  statement applies to the entire array.  For example:

    INTEGER, DIMENSION(2:11,3) :: L   ! Specifies the type and
                                      !    dimensions of array L

  If a whole array appears in an executable statement, the statement
  applies to all of the elements in the array.  For example:

    L = 10             ! The value 10 is assigned to all the
                       !   elements in array L

    WRITE *, L         ! Prints all the elements in array L

1.3  –  Subscripts

  Arrays can be referenced by individual elements or by a range of
  elements (array sections).  A subscript list (appended to the array
  name) indicates which array element or array section is being
  referenced.

  In the subscript list for an array section, at least one of the
  subscripts must be a subscript triplet or vector subscript.

  VSI Fortran permits intrinsic noninteger expressions for
  subscripts, but they are converted to integers before use (any
  fractional parts are truncated).

1.4  –  Elements

  An array element is one of the scalar data items that make up an
  array.  A subscript list (appended to the array or array component)
  determines which element is being referred to.  A reference to an
  array element takes the following form:

    array [(s-list)]

      array   Is the name of an array.

      s-list  Is a list of one or more subscripts. The
              number of subscripts must equal the rank of
              the array.

              Each subscript must be a scalar numeric
              expression with a value that is within the
              bounds of its dimension.

  Each array element inherits the type, kind type parameter, and
  certain attributes (INTENT, PARAMETER, and TARGET) of the parent
  array.  An array element cannot inherit the POINTER attribute.

  If an array element is of type character, it can be followed by a
  substring range in parentheses; for example:

    ARRAY_D(1,2) (1:3)    ! elements are substrings of length 3

  However, by convention, such an object is considered to be a
  substring rather than an array element.

  The following are some valid array element references for an array
  declared as REAL B(10,20):  B(1,3), B(10,10), and B(5,8).

  For information on arrays as structure components, see DATA DERIVED
  COMP in online Help.

1.4.1  –  Order of Elements

  The elements of an array form a sequence known as the array element
  order.  The position of an element in this sequence is its
  subscript order value.

  The elements of an array are stored as a linear sequence of values.
  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.  This is called the
  order of subscript progression.

  In an array section, the subscript order of the elements is their
  order within the section itself.  For example, if an array is
  declared as B(20), the section B(4:19:4) consists of elements B(4),
  B(8), B(12), and B(16).  The subscript order value of B(4) in the
  array section is 1; the subscript order value of B(12) in the
  section is 3.

1.5  –  Sections

  An array section is a portion of an array that is an array itself.
  It is an array subobject.  A section subscript list (appended to
  the array or array component) determines which portion is being
  referred to.  A reference to an array section takes the following
  form:

     array [(sect-s-list)] [(substring-range)]

     array            Is the name of an array.

     sect-s-list      Is a list of one or more section
                      subscripts (subscripts, subscript
                      triplets, or vector subscripts)
                      indicating a set of elements along
                      a particular dimension.

                      At least one of the items in the section
                      subscript list must be a subscript
                      triplet or vector subscript. Each
                      subscript and subscript triplet must be
                      a scalar numeric expression. Each vector
                      subscript must be a rank-one integer
                      expression.

     substring-range  Is a substring range in the form
                      [expr]:[expr].  Each expression specified
                      must be a scalar numeric expression.

                      The array (or array component) preceding
                      the substring range must be of type character.

  If no section subscript list is specified, the rank and shape of
  the array section is the same as the parent array.

  Otherwise, the rank of the array section is the number of vector
  subscripts and subscript triplets that appear in the list.  Its
  shape is a rank-one array where each element is the number of
  integer values in the sequence indicated by the corresponding
  subscript triplet or vector subscript.

  If any of these sequences is empty, the array section has a size of
  zero.  The subscript order of the elements of an array section is
  that of the array object that the array section represents.

  Each array section inherits the type, kind type parameter, and
  certain attributes (INTENT, PARAMETER, and TARGET) of the parent
  array.  An array section cannot inherit the POINTER attribute.

  The following shows valid references to array sections:

    REAL, DIMENSION(20) :: B
    ...
    PRINT *, B(2:20:5)  ! the section consists of elements
                        !     B(2), B(7), B(12), and B(17)
    K = (/3, 1, 4/)

    B(K) = 0.0  ! section B(K) is a rank-one array with
                ! shape (3) and size 3. (0.0 is assigned to
                ! B(1), B(3), and B(4).)

  Consider the following declaration:

    CHARACTER(LEN=15) C(10,10)

  An array section referenced as C(:,:)(1:3) is an array of shape
  (10,10) whose elements are substrings of length 3 of the
  corresponding elements of C.

1.5.1  –  Triplets

  A subscript triplet consists of three parts:  the first two parts
  designate a range of subscript values and the third part designates
  the increment (stride) between each value.  It takes the following
  form:

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

    subscript-1   Is a scalar numeric expression representing
                  the first value in the subscript sequence.
                  If omitted, the declared lower bound of the
                  dimension is used.

    subscript-2   Is a scalar numeric expression representing
                  the last value in the subscript sequence.
                  If omitted, the declared upper bound of the
                  dimension is used.

                  When indicating sections of an assumed-size
                  array, this subscript must be specified.

    stride        Is a scalar numeric expression representing
                  the increment between successive subscripts
                  in the sequence.  It must have a nonzero value.
                  If it is omitted, it is assumed to be 1.

  The stride has the following effects:

   o  If the stride is positive, the subscript range starts with the
      first subscript and is incremented by the value of the stride,
      until the largest value less than or equal to the second
      subscript is attained.

      For example, if an array has been declared as B(6,3,2), the
      array section specified as B(2:4,1:2,2) is a rank-two array
      with shape (3,2) and size 6.  It consists of the following six
      elements:

          B(2,1,2)   B(2,2,2)
          B(3,1,2)   B(3,2,2)
          B(4,1,2)   B(4,2,2)

      If the first subscript is greater than the second subscript,
      the range is empty.

   o  If the stride is negative, the subscript range starts with the
      value of the first subscript and is decremented by the absolute
      value of the stride, until the smallest value greater than or
      equal to the second subscript is attained.

      For example, if an array has been declared as A(15), the array
      section specified as A(10:3:-2) is a rank-one array with shape
      (4) and size 4.  It consists of the following four elements:

          A(10)
          A(8)
          A(6)
          A(4)

      If the second subscript is greater than the first subscript,
      the range is empty.

  If a range specified by the stride is empty, the array section has
  a size of zero.

  A subscript in a subscript triplet need not be within the declared
  bounds for that dimension if all values used to select the array
  elements are within the declared bounds.  For example, if an array
  has been declared as A(15), the array section specified as
  A(4:16:10) is valid.  The section is a rank-one array with shape
  (2) and size 2.  It consists of elements A(4) and A(14).

  If the subscript triplet does not specify bounds or stride, but
  only a colon (:), the entire declared range for the dimension is
  used.

1.5.2  –  Vector Subscripts

  A vector subscript is a rank-one array of integer values (within
  the declared bounds for the dimension).  It is used to select a
  sequence of elements from a parent array.  The sequence does not
  have to be in order, and it can contain duplicate values.

  For example, A is a rank-two array of shape (4,6).  B and C are
  rank-one arrays of shape (2) and (3), respectively, with the
  following values:

    B = (/1,4/)
    C = (/2,1,1/)         ! Will result in a many-one
                          !   array section

  Array section A(3,B) consists of elements A(3,1) and A(3,4).  Array
  section A(C,1) consists of elements A(2,1), A(1,1), and A(1,1).
  Array section A(B,C) consists of the following elements:

    A(1,2)   A(1,1)   A(1,1)
    A(4,2)   A(4,1)   A(4,1)

  An array section with a vector subscript that has two or more
  elements with the same value is called a many-one array section.  A
  many-one section must not appear on the left of the equals sign in
  an assignment statement, or as an input item in a READ statement.

  The following assignments to C also show examples of vector
  subscripts:

    INTEGER A(2), B(2), C(2)
    ...
    B    = (/1,2/)
    C(B) = A(B)
    C    = A((/1,2/))

  An array section with a vector subscript must not be any of the
  following:

   o  An internal file

   o  An actual argument associated with a dummy array that is
      defined or redefined (if the INTENT attribute is specified, it
      must be INTENT(IN))

   o  The target in a pointer assignment statement

  If the sequence specified by the vector subscript is empty, the
  array section has a size of zero.

1.6  –  Constructors

  An array constructor is a sequence of scalar values that is
  interpreted as a rank-one array.  The array element values are
  those specified in the sequence.  An array constructor takes the
  following form:

     (/ac-value-list/)

     ac-value-list  Is a list of one or more expressions
                    or implied-do loops. Each ac-value must
                    have the same type and kind type parameter.

  An implied-do loop in an array constructor takes the following
  form:

    (ac-value-expr, do-variable = expr1, expr2 [,expr3])

    ac-value-expr  Is a scalar expression evaluated for each
                   value of the d-variable to produce an array
                   element value.

    do-variable    Is the name of a scalar integer variable.
                   Its scope is that of the implied-do loop.

    expr           Is a scalar integer expression. The expr1
                   and expr2 specify a range of values for
                   the loop; expr3 specifies the stride.

  The array constructor has the same type as the ac-value-list
  expressions.

  If the sequence of values specified by the array constructor is
  empty (there are no expressions or the implied-do loop produces no
  values), the rank-one array has a size of zero.

  The ac-value specifies the following:

   o  If it is a scalar expression, its value specifies an element of
      the array constructor.

   o  If it is an array expression, the values of the elements of the
      expression, in array element order, specify the corresponding
      sequence of elements of the array constructor.

   o  If it is an implied-do loop, it is expanded to form an array
      constructor value sequence under the control of the DO
      variable, as in the DO construct.

  If every expression in an array constructor is a constant
  expression, the array constructor is a constant expression.

  If an implied-do loop is contained within another implied-do loop
  (nested), they cannot have the same DO variable (do-variable).

  There are three forms for an ac-value, as follows:

    C1 = (/4,8,7,6/)                  ! A scalar expression
    C2 = (/B(I, 1:5), B(I:J, 7:9)/)   ! An array expression
    C3 = (/(I, I=1, 4)/)              ! An implied-do loop

  You can also mix these forms, for example:

    C4 = (/4, A(1:5), (I, I=1, 4), 7/)

  To define arrays of more than one dimension, use the RESHAPE
  intrinsic function.

  The following are alternative forms for array constructors:

   o  Square brackets (instead of parentheses and slashes) to enclose
      array constructors; for example, the following two array
      constructors are equivalent:

        INTEGER C(4)
        C = (/4,8,7,6/)
        C = [4,8,7,6]

   o  A colon-separated triplet (instead of an implied-do loop) to
      specify a range of values and a stride; for example, the
      following two array constructors are equivalent:

        INTEGER D(3)
        D = (/1:5:2/)              ! Triplet form
        D = (/(I, I=1, 5, 2)/)     ! Implied-do loop form

  The following example shows an array constructor using an
  implied-do loop:

    INTEGER ARRAY_C(10)
    ARRAY_C = (/(I, I=30, 48, 2)/)

  The values of ARRAYC are the even numbers 30 through 48.

  The following example shows an array constructor of derived type
  that uses a structure constructor:

    TYPE EMPLOYEE
      INTEGER ID
      CHARACTER(LEN=30) NAME
    END TYPE EMPLOYEE

    TYPE(EMPLOYEE) CC_4T(4)
    CC_4T = (/EMPLOYEE(2732,"JONES"), EMPLOYEE(0217,"LEE"),     &
              EMPLOYEE(1889,"RYAN"), EMPLOYEE(4339,"EMERSON")/)

  The following example shows how the RESHAPE intrinsic function is
  used to create a multidimensional array:

    E = (/2.3, 4.7, 6.6/)
    D = RESHAPE(SOURCE = (/3.5,(/2.0,1.0/),E/), SHAPE = (/2,3/))

  D is a rank-two array with shape (2,3) containing the following
  elements:

    3.5   1.0   4.7
    2.0   2.3   6.6

1.7  –  Dynamic Data

  Allocatable arrays and pointer targets can be dynamically allocated
  (created) and deallocated (freed), by using the ALLOCATE and
  DEALLOCATE statements, respectively.

  Pointers are associated with targets by pointer assignment or by
  allocating the target.  They can be dynamically disassociated from
  targets by using the NULLIFY statement.

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

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

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

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

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

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

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

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

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

2.9.1  –  DOUBLE_PRECISION

  See DATA CONSTANTS REAL REAL_8 in this Help file.

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

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

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

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

3  –  Derived Types

  Like intrinsic data types, a Fortran 95/90 derived data type has a
  name, a set of associated values, a way to denote the values, and
  operations to manipulate and interpret these values.

  The names of the intrinsic data types are predefined, while the
  names of derived types are defined in derived-type definitions.

  A derived-type definition specifies the name of the type and the
  types of its components.  A derived type can be resolved into
  "ultimate" components that are either of intrinsic type or are
  pointers.

  The set of values for a specific derived type consists of all
  possible sequences of component values permitted by the definition
  of that derived type.  Structure constructors are used to specify
  values of derived types.

  Nonintrinsic assignment for derived-type entities must be defined
  by a subroutine with an ASSIGNMENT interface.  Any operation on
  derived-type entities must be defined by a function with an
  OPERATOR interface.  Arguments and function values can be of any
  intrinsic or derived type.

3.1  –  Type Definitions

  A derived-type definition specifies the name of a user-defined type
  and the types of its components.  It takes the following form:

    TYPE [[, PRIVATE or PUBLIC] :: ] name
      [PRIVATE or SEQUENCE]...
      comp-def
      [comp-def]...
    END TYPE [name]

    name      Is the name of the derived type. It must not be
              the same as the name of any intrinsic type, or
              the same as the name of a derived type that can be
              accessed from a module.

    comp-def  There must be at least one.  It takes the following
              form:

       type [ [, attr-list] ::] comp [(a-spec)] [*char-len] [init_ex]

    type      Is a type specifier.  It can be an intrinsic type
              or a previously defined derived type. (If the POINTER
              attribute follows this specifier, the type can also be
              any accessible derived type, including the type
              being defined.)

    attr-list Is an optional list of component attributes POINTER
              or DIMENSION.  You can specify one or both attributes.
              If DIMENSION is specified, it can be followed by an
              array specification.

    comp      Is the name of the component being defined.

    a-spec    Is an optional array specification, enclosed in
              parentheses.  If POINTER is specified, the array is
              deferred-shape; otherwise, it is explicit-shape.

              In an explicit-shape specification, each bound must
              be a constant scalar integer expression.

    char-len  Is an optional scalar integer literal constant; it
              must be preceded by an asterisk (*).  This parameter
              can only be specified if the component is of type
              CHARACTER.

    init_ex   Is an initialization expression or, for pointer
              objects, =>NULL().

  If a name is specified following the END TYPE statement, it must be
  the same name that follows TYPE in the derived type statement.

  Within a scoping unit, a derived-type name can only be defined
  once.  If the same derived-type name appears in a derived-type
  definition in another scoping unit, it is treated independently.

  A component name has the scope of the derived-type definition only.
  Therefore, the same name can be used in another derived-type
  definition in the same scoping unit.

  Two entities can have the same derived type in the following cases:

   o  If they are both declared to be of the same derived type, and
      the derived-type definition can be accessed from the same
      module, the same scoping unit, or a host scoping unit.

   o  If they are both declared to be of the same derived type, and
      the derived-type definition can be accessed from the same
      scoping unit or a host scoping unit.

   o  If they are both declared in a derived-type definition
      specifying SEQUENCE (they both have sequence type).

      A sequence type can be defined in each scoping unit that needs
      to access the type.  Each derived-type definition must specify
      the same name, the keyword SEQUENCE, and have components that
      agree in order, name, and attributes.  (No private components
      are allowed in a sequence type.)

  The same PRIVATE or SEQUENCE statements can only appear once in a
  given derived-type definition.

  If SEQUENCE is present, all derived types specified in component
  definitions must be sequence types.

  The PUBLIC or PRIVATE keywords can only appear if the derived-type
  definition is in the specification part of a module.

  The POINTER or DIMENSION attribute can only appear once in a given
  comp-def.

  A component is an array if the component definition contains a
  DIMENSION attribute or an array specification.  If the component
  definition contains an array specification, the array bounds should
  be specified there; otherwise, they must be specified following the
  DIMENSION attribute.

  If an initialization expression ("init_ex") appears for a
  nonpointer component, the component (in any object of the type) is
  initially defined with the value determined from the initialization
  expression.  The initialization expression is evaluated in the
  scoping unit of the type definition.

  The initialization expression overrides any default initial value
  specified for the component.  Explicit initialization in a type
  declaration statement overrides default initialization.

  If POINTER appears in the comp-def, the component is a pointer.
  Pointers can have an association status of associated,
  disassociated, or undefined.  If no default initialization status
  is specified, the status of the pointer is undefined.  To specify
  disassociated status for a pointer component, use =>NULL().

3.2  –  Components

  A reference to a component of a derived-type structure takes the
  following form:

    parent [%component [(s-list)]]... %component [(s-list)]

    parent    Is the name of a scalar or array of derived type.
              The percent sign (%) is called a component selector.

    component Is the name of a component of the immediately
              preceding parent or component.

    s-list    Is a list of one or more subscripts. If the list
              contains subscript triplets or vector subscripts,
              the reference is to an array section.

              Each subscript must be a scalar numeric expression
              with a value that is within the bounds of its
              dimension.

              The number of subscripts in any s-list must equal
              the rank of the immediately preceding parent or
              component.

  Each parent or component (except the rightmost) must be of derived
  type.

  The parent or one of the components can have nonzero rank (be an
  array).  Any component to the right of a parent or component of
  nonzero rank must not have the POINTER attribute.

  The rank of the structure component is the rank of the part (parent
  or component) with nonzero rank (if any); otherwise, the rank is
  zero.  The type and type parameters (if any) of a structure
  component are those of the rightmost part name.

  The structure component must not be referenced or defined before
  the declaration of the parent object.

  If the parent object has the INTENT, TARGET, or PARAMETER
  attribute, the structure component also has the attribute.

3.2.1  –  Examples

  The following example shows a derived-type definition with two
  components:

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

  The following shows how to declare a variable CONTRACT of type
  EMPLOYEE:

    TYPE(EMPLOYEE) :: CONTRACT

  Note that both examples started with the keyword TYPE.  The first
  (initial) statement of a derived-type definition is called a
  derived-type statement, while the statement that declares a
  derived-type object is called a TYPE statement.

  The following example shows how to reference component ID of parent
  structure CONTRACT:

    CONTRACT%ID

  The following example shows a derived type with a component that is
  a previously defined type:

    TYPE DOT
      REAL X, Y
    END TYPE DOT
    ....
    TYPE SCREEN
      TYPE(DOT) C, D
    END TYPE SCREEN

  The following declares a variable of type SCREEN:

    TYPE(SCREEN) M

  Variable M has components M%C and M%D (both of type DOT); M%C has
  components M%C%X and M%C%Y of type REAL.

  The following example shows a derived type with a component that is
  an array:

    TYPE CAR_INFO
      INTEGER YEAR
      CHARACTER(LEN=15), DIMENSION(10) :: MAKER
      CHARACTER(LEN=10) MODEL, BODY_TYPE*8
      REAL PRICE
    END TYPE
    ...
    TYPE(CAR_INFO) MY_CAR

  Note that MODEL has a character length of 10, but BODYTYPE has a
  character length of 8.  You can assign a value to a component of a
  structure; for example:

    MY_CAR%YEAR = 1985

  The following shows an array structure component:

    MY_CAR%MAKER

  In the preceding example, if a subscript list (or substring) was
  appended to MAKER, the reference would not be to an array structure
  component, but to an array element or section.

  Consider the following:

    TYPE CHARGE
      INTEGER PARTS(40)
      REAL LABOR
      REAL MILEAGE
    END TYPE CHARGE

    TYPE(CHARGE) MONTH
    TYPE(CHARGE) YEAR(12)

  Some valid array references for this type follow:

    MONTH%PARTS(I)           ! An array element
    MONTH%PARTS(I:K)         ! An array section
    YEAR(I)%PARTS            ! An array structure component
                             !  (a whole array)

    YEAR(J)%PARTS(I)         ! An array element
    YEAR(J)%PARTS(I:K)       ! An array section
    YEAR(J:K)%PARTS(I)       ! An array section
    YEAR%PARTS(I)            ! An array section

  The following example shows a derived type with a pointer component
  that is of the type being defined:

    TYPE NUMBER
      INTEGER NUM
      TYPE(NUMBER), POINTER :: BEFORE_NUM
      TYPE(NUMBER), POINTER :: AFTER_NUM
    END TYPE

  A type such as this can be used to construct linked lists of
  objects of type NUMBER.

  The following example shows a private type:

    TYPE, PRIVATE :: SYMBOL
      LOGICAL TEST
      CHARACTER(LEN=50) EXPLANATION
    END TYPE SYMBOL

  This type is private to the module.  The module can be used by
  another scoping unit, but type SYMBOL is not available.

  The following example shows a derived-type definition that is
  public with components that are private:

    MODULE MATTER
      TYPE ELEMENTS
        PRIVATE
        INTEGER C, D
      END TYPE
    ...
    END MODULE MATTER

  In this case, components C and D are private to type ELEMENTS, but
  type ELEMENTS is not private to MODULE MATTER.  Any program unit
  that uses the module MATTER can declare variables of type ELEMENTS,
  and pass as arguments values of type ELEMENTS.

  This design allows you to change components of a type without
  affecting other program units that use the module.

  If a derived type is needed in more than one program unit, the
  definition should be placed in a module and accessed by a USE
  statement whenever it is needed, as follows:

    MODULE STUDENTS
      TYPE STUDENT_RECORD
      ...
      END TYPE
    CONTAINS
      SUBROUTINE COURSE_GRADE(...)
      TYPE(STUDENT_RECORD) NAME
      ...
      END SUBROUTINE
    END MODULE STUDENTS
    ...

    PROGRAM SENIOR_CLASS
      USE STUDENTS
      TYPE(STUDENT_RECORD) ID
      ...
    END PROGRAM

  Program SENIOR_CLASS has access to type STUDENT_RECORD, because it
  uses module STUDENTS.  Module procedure COURSE_GRADE also has
  access to type STUDENT_RECORD, because the derived-type definition
  appears in its host.

3.3  –  Constructors

  A structure constructor lets you specify scalar values of a derived
  type.  It takes the following form:

    d-name (expr-list)

    d-name    Is the name of the derived type.

    expr-list Is a list of expressions specifying component
              values.  The values must agree in number and
              order with the components of the derived type.

              If necessary, values are converted (according
              to the rules of assignment), to agree with their
              corresponding components in type and kind type
              parameters.

  A structure constructor must not appear before its derived type is
  defined.

  If a component of the derived type is an array, the shape in the
  expression list must conform to the shape of the component array.

  If a component of the derived type is a pointer, the value in the
  expression list must evaluate to an object that would be a valid
  target in a pointer assignment statement.  (A constant is not a
  valid target in a pointer assignment statement.)

  If all the values in a structure constructor are constant
  expressions, the constructor is a derived-type constant expression.

3.3.1  –  Examples

  Consider the following derived-type definition:

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

  This can be used to produce the following structure constructor:

    EMPLOYEE(3472, "John Doe")

  The following example shows a type with a component of derived
  type:

    TYPE ITEM
      REAL COST
      CHARACTER(LEN=30) SUPPLIER
      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