XL Fortran for AIX 8.1

Language Reference


Array Sections

An array section is a selected portion of an array. It is an array subobject that designates a set of elements from an array, or a specified substring or derived-type component from each of those elements. An array section is also an array.

Note:
This introductory section describes the simple case, where structure components are not involved. Array Sections and Structure Components explains the additional rules for specifying array sections that are also structure components.



>>---array_name--(--section_subscript_list--)--+-----------------+---><
                                               '-substring_range-'
 
 

section subscript:

>>-+-subscript---------+---------------------------------------><
   +-subscript_triplet-+
   '-vector_subscript--'
 
 

section_subscript
designates some set of elements along a particular dimension. It can be composed of a combination of the following:

subscript
is a scalar integer expression, explained in Array Elements.

+-------------------------------IBM Extension--------------------------------+

A subscript is a real expression in XL Fortran.

+----------------------------End of IBM Extension----------------------------+

subscript_triplet, vector subscript
designate a (possibly empty) sequence of subscripts in a given dimension. For details, see Subscript Triplets and Vector Subscripts.

Note:
At least one of the dimensions must be a subscript triplet or vector subscript, so that an array section is distinct from an array element:
INTEGER, DIMENSION(5,5,5) :: A
A(1,2,3) = 100
A(1,3,3) = 101
PRINT *, A(1,2,3)    ! A single array element, 100.
PRINT *, A(1,2:2,3)  ! A one-element array section, (/ 100 /)
PRINT *, A(1,2:3,3)  ! A two-element array section, (/ 100, 101 /)

substring_range



>>-(--+-----------+--:--+-----------+--)-----------------------><
      '-int_expr1-'     '-int_expr2-'
 
 

int_expr1 and int_expr2 are scalar integer expressions called substring expressions, defined in Character Substrings. They specify the leftmost and rightmost character positions, respectively, of a substring of each element in the array section. If an optional substring_range is present, the section must be from an array of character objects.

An array section is formed from the array elements specified by the sequences of values from the individual subscripts, subscript triplets, and vector subscripts, arranged in column-major order.

For example, if SECTION = A( 1:3, (/ 5,6,5 /), 4 ):

The sequence of numbers for the first dimension is 1, 2, 3.
The sequence of numbers for the second dimension is 5, 6, 5.
The subscript for the third dimension is the constant 4.

The section is made up of the following elements of A, in this order:

A(1,5,4)   |                        |        SECTION(1,1)
A(2,5,4)   |----- First column -----|        SECTION(2,1)
A(3,5,4)   |                        |        SECTION(3,1)
A(1,6,4)     |                        |      SECTION(1,2)
A(2,6,4)     |----- Second column ----|      SECTION(2,2)
A(3,6,4)     |                        |      SECTION(3,2)
A(1,5,4)       |                        |    SECTION(1,3)
A(2,5,4)       |----- Third column -----|    SECTION(2,3)
A(3,5,4)       |                        |    SECTION(3,3)

Some examples of array sections include:

INTEGER, DIMENSION(10,20) :: A
! These references to array sections require loops or multiple
! statements in FORTRAN 77.
PRINT *, A(1:5,1)                   ! Contiguous sequence of elements
PRINT *, A(1:20:2,10)               ! Noncontiguous sequence of
elements
PRINT *, A(:,5)                     ! An entire column
PRINT *, A( (/1,10,5/), (/7,3,1/) ) ! A 3x3 assortment of elements

Related Information:
Structure Components.

Subscript Triplets

A subscript triplet consists of two subscripts and a stride, and defines a sequence of numbers corresponding to array element positions along a single dimension.



>>-+------------+--:--+------------+--+-----------+------------><
   '-subscript1-'     '-subscript2-'  '-:--stride-'
 
 

subscript1, subscript2
are subscripts that designate the first and last values in the sequence of indices for a dimension.

If the first subscript is omitted, the lower array bound of that dimension is used. If the second subscript is omitted, the upper array bound of that dimension is used. (The second subscript is mandatory for the last dimension when specifying sections of an assumed-size array.)

stride
is a scalar integer expression that specifies how many subscript positions to count to reach the next selected element.

IBM Extension BeginsA stride is a real expression in XL Fortran. IBM Extension Ends

If the stride is omitted, it has a value of 1. The stride must have a nonzero value:

Calculations of values in the sequence use the same steps as shown in Executing a DO Statement.

A subscript in a subscript triplet does not have to be within the declared bounds for that dimension if all the values used in selecting the array elements for the array section are within the declared bounds:

INTEGER A(9)
PRINT *, A(1:9:2)  ! Count from 1 to 9 by 2s: 1, 3, 5, 7, 9.
PRINT *, A(1:10:2) ! Count from 1 to 10 by 2s: 1, 3, 5, 7, 9.
                   ! No element past A(9) is specified.

Examples of Subscript Triplets

REAL, DIMENSION(10) :: A
INTEGER, DIMENSION(10,10) :: B
CHARACTER(10) STRING(1:100)
 
PRINT *, A(:)                 ! Print all elements of array.
PRINT *, A(:5)                ! Print elements 1 through 5.
PRINT *, A(3:)                ! Print elements 3 through 10.
 
PRINT *, STRING(50:100)       ! Print all characters in
                              ! elements 50 through 100.
 
! The following statement is equivalent to A(2:10:2) = A(1:9:2)
A(2::2) = A(:9:2)             ! LHS = A(2), A(4), A(6), A(8), A(10)
                              ! RHS = A(1), A(3), A(5), A(7), A(9)
                              ! The statement assigns the odd-numbered
                              ! elements to the even-numbered elements.
 
! The following statement is equivalent to PRINT *, B(1:4:3,1:7:6)
PRINT *, B(:4:3,:7:6)         ! Print B(1,1), B(4,1), B(1,7), B(4,7)
 
PRINT *, A(10:1:-1)           ! Print elements in reverse order.
 
PRINT *, A(10:1:1)            ! These two are
PRINT *, A(1:10:-1)           ! both zero-sized.
END

Vector Subscripts

A vector subscript is an integer array expression of rank one, designating a sequence of subscripts that correspond to the values of the elements of the expression.

IBM Extension BeginsA vector subscript is a real array expression in XL Fortran. IBM Extension Ends

The sequence does not have to be in order, and may contain duplicate values:

INTEGER A(10), B(3), C(3)
PRINT *, A( (/ 10,9,8 /) ) ! Last 3 elements in reverse order
B = A( (/ 1,2,2 /) )       ! B(1) = A(1), B(2) = A(2), B(3) = A(2) also
END
An array section with a vector subscript in which two or more elements of the vector subscript have the same value is called a many-one section. Such a section must not:

Notes:

  1. An array section used as an internal file must not have a vector subscript.

  2. If you pass an array section with a vector subscript as an actual argument, the associated dummy argument must not be defined or redefined.

  3. An array section with a vector subscript must not be the target in a pointer assignment statement.
! We can use the whole array VECTOR as a vector subscript for A and B
INTEGER, DIMENSION(3) :: VECTOR= (/ 1,3,2 /), A, B
INTEGER, DIMENSION(4) :: C = (/ 1,2,4,8 /)
A(VECTOR) = B            ! A(1) = B(1), A(3) = B(2), A(2) = B(3)
A = B( (/ 3,2,1 /) )     ! A(1) = B(3), A(2) = B(2), A(3) = B(1)
PRINT *, C(VECTOR(1:2))  ! Prints C(1), C(3)
END

Array Sections and Substring Ranges

For an array section with a substring range, each element in the result is the designated character substring of the corresponding element of the array section. The rightmost array name or component name must be of type character.

PROGRAM SUBSTRING
TYPE DERIVED
  CHARACTER(10) STRING(5)       ! Each structure has 5 strings of 10 chars.
END TYPE DERIVED
TYPE (DERIVED) VAR, ARRAY(3,3)  ! A variable and an array of derived type.
 
VAR%STRING(:)(1:3) = 'abc'      ! Assign to chars 1-3 of elements 1-5.
VAR%STRING(3:)(4:6) = '123'     ! Assign to chars 4-6 of elements 3-5.
 
ARRAY(1:3,2)%STRING(3)(5:10) = 'hello'
                                ! Assign to chars 5-10 of the third element in
                                ! ARRAY(1,2)%STRING, ARRAY(2,2)%STRING, and
END                             ! ARRAY(3,2)%STRING

Array Sections and Structure Components

To understand how array sections and structure components overlap, you should be familiar with the syntax for Structure Components.

What we defined at the beginning of this section as an array section is really only a subset of the possible array sections. An array name or array name with a section_subscript_list can be a subobject of a structure component:

struct_sect_subobj:



>>-object_name--+------------------------------+---------------->
                '-(--section_subscript_list--)-'
 
   .----------------------------------------------------.
   V                                                    |
>----+-%-+--comp_name--+------------------------------+-+------->
     '-.-'             '-(--section_subscript_list--)-'
 
>--+-----------------+-----------------------------------------><
   '-substring_range-'
 
 

object_name
is the name of an object of derived type

section_subscript_list, substring_range
are the same as defined under Array Sections

comp_name
is the name of a derived-type component

% or .
Separator character.
Note:
The . (period) separator is an IBM extension.

Notes:

  1. The type of the last component determines the type of the array.

  2. Only one part of the structure component may have nonzero rank. Either the rightmost comp_name must have a section_subscript_list with nonzero rank, or another part must have nonzero rank.

  3. Any parts to the right of the part with nonzero rank must not have the POINTER attribute.
TYPE BUILDING_T
  LOGICAL RESIDENTIAL
END TYPE BUILDING_T
TYPE STREET_T
  TYPE (BUILDING_T) ADDRESS(500)
END TYPE STREET_T
TYPE CITY_T
  TYPE (STREET_T) STREET(100,100)
END TYPE CITY_T
TYPE (CITY_T) PARIS
TYPE (STREET_T) S
TYPE (BUILDING_T) RESTAURANT
! LHS is not an array section, no subscript triplets or vector subscripts.
PARIS%STREET(10,20) = S
! None of the parts are array sections, but the entire construct
!   is a section because STREET has a nonzero rank and is not
!   the rightmost part.
PARIS%STREET%ADDRESS(100) = BUILDING_T(.TRUE.)
 
! STREET(50:100,10) is an array section, making the LHS an array section
!   with rank=2, shape=(/51,10/).
! ADDRESS(123) must not be an array section because only one can appear
!   in a reference to a structure component.
PARIS%STREET(50:100,10)%ADDRESS(123)%RESIDENTIAL = .TRUE.
END

Rank and Shape of Array Sections

For an array section that is not a subobject of a structure component, the rank is the number of subscript triplets and vector subscripts in the section_subscript_list. The number of elements in the shape array is the same as the number of subscript triplets and vector subscripts, and each element in the shape array is the number of integer values in the sequence designated by the corresponding subscript triplet or vector subscript.

For an array section that is a subobject of a structure component, the rank and shape are the same as those of the part of the component that is an array name or array section.

DIMENSION :: ARR1(10,20,100)
TYPE STRUCT2_T
  LOGICAL SCALAR_COMPONENT
END TYPE
TYPE STRUCT_T
  TYPE (STRUCT2_T), DIMENSION(10,20,100) :: SECTION
END TYPE
 
TYPE (STRUCT_T) STRUCT
 
! One triplet + one vector subscript, rank = 2.
! Triplet designates an extent of 10, vector subscript designates
!   an extent of 3, thus shape = (/ 10,3 /).
ARR1(:, (/ 1,3,4 /), 10) = 0
 
! One triplet, rank = 1.
! Triplet designates 5 values, thus shape = (/ 5 /).
STRUCT%SECTION(1,10,1:5)%SCALAR_COMPONENT = .TRUE.
 
! Here SECTION is the part of the component that is an array,
!   so rank = 3 and shape = (/ 10,20,100 /), the same as SECTION.
STRUCT%SECTION%SCALAR_COMPONENT = .TRUE.


[ Top of Page | Previous Page | Next Page | Table of Contents | Index ]