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

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

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

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.

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.

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.

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.

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.

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

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.
Close Help