Another technique for referencing table elements is indexing. Indexing is made possible by supplying the INDEXED BY phrase in the OCCURS clause.
The index does not require its own data description entry. At object time, the value of an index is a binary value representing a displacement from the beginning of the table. The value of this binary number is calculated from the number and length of the table element as follows:
binary value of index = (occurrence number -
1) * length of table element
The value of an index may only be set using the SET, SEARCH or PERFORM statement. The initial value is undefined and must be set explicitly.
There are two forms of indexing:
direct indexing
relative indexing
Direct indexing
Direct indexing obtains when an index is used in the manner of a direct subscript.
Example 2-18
01 TABLE1. 02 TABLE-A PIC XX OCCURS 10 TIMES INDEXED BY INDEX-A. 02 TABLE-B PIC X(3) OCCURS 5 TIMES INDEXED BY INDEX-B. . . SET INDEX-A TO 7. . MOVE "X7" TO TABLE-A (INDEX-A).
Two tables are defined here:
TABLE-A with 10 elements, each 2 bytes long
TABLE-B with 5 elements, each 3 bytes long
INDEX-A is declared for TABLE-A and INDEX-B is declared for TABLE-B by means of the INDEXED BY phrase. Indices may only be used with the corresponding elementary item, e.g. TABLE-A(INDEX-A) or TABLE-B(INDEX-B).
The SET statement sets the index to a value that points to the seventh element of TABLE-A. The displacement from the start of the table, i.e. the internal binary contents of INDEX-A, is (7-
1) *
2 = 12. Thus, the MOVE statement transfers X7 to the seventh table element.
Relative indexing
When the name of a table element is followed by an index in the form
(index + integer-1),
then the required occurrence number is calculated from the value of index-name at object time, plus integer-1.
If the form
(index - integer-2),
is used, then the new occurrence number is obtained by subtracting integer-2 from the corresponding current occurrence number.
The use of relative indexing will not change the values of the index-names in the object program.
Permissible value ranges for indices
As specified in the standard, the value of an index should correspond to a valid occurrence number of the associated table. This compiler also permits corresponding occurrence numbers for 0, ZERO, or negative numbers, and values beyond the maximum permissible occurrence numbers, if the binary value of the index remains within the range (representable in 4 bytes) -
231 to +231 -
1. In these cases, the index must be set (e.g. with SET UP or SET DOWN) to a valid occurrence number before it is used, or corresponding relative indexing must be used to ensure that only valid table elements are addressed.