A table element is indicated in the data description entry by specifying the OCCURS clause. This clause defines how many elements the table contains. The name and description of the table item apply to each recurrence thereof. In the case of multi-dimensional tables, each dimension in the hierarchical structure must be given an OCCURS clause.
Example 2-13
01 TABLE1. 02 TABLE-ELEMENT PIC XXX OCCURS 20 TIMES.
The data item TABLE1 comprises 20 data items of identical length. These items are given the name TABLE-ELEMENT:
TABLE1: 1. TABLE-ELEMENT (1) PIC XXX. 2. TABLE-ELEMENT (2) PIC XXX. . . . 20. TABLE-ELEMENT (20) PIC XXX.
One-dimensional tables
The OCCURS clause is entered in the data description entry of the table element.
Example 2-14
01 TABLE2. 02 TABLE-ELEMENT OCCURS 2 TIMES. 03 ELEMENT-ITEM-1 PIC X(4). 03 ELEMENT-ITEM-2 PIC X(4).
TABLE2 is the name of the table.
TABLE-ELEMENT is the element which occurs twice within the one-dimensional TABLE2.
ELEMENT-ITEM-1 and ELEMENT-ITEM-2 are elements which are subordinate to TABLE-ELEMENT.
Multi-dimensional tables
When a data item is subordinate to a table-element within a two-dimensional table and contains an OCCURS clause, then this data item is an element within a three-dimensional table.
Up to seven dimensions are allowed for a single table.
Example 2-15
01 TABLE3. 02 BLK OCCURS 2 TIMES. 03 RECORD OCCURS 2 TIMES. 04 ITEM OCCURS 2 TIMES PIC X(10).
BLK is an element which occurs twice within a one-dimensional table.
RECORD is an element in a two-dimensional table. It occurs twice within each occurrence of BLK.
ITEM is an element in a three-dimensional table. It occurs twice within each occurrence of RECORD.
TABLE |
BLK (1) |
RECORD (1, 1) |
ITEM (1, 1, 1) |
ITEM (1, 1, 2) |
|||
RECORD (1, 2) |
ITEM (1, 2, 1) |
||
ITEM (1, 2, 2) |
|||
BLK (2) |
RECORD (2, 1) |
ITEM (2, 1, 1) |
|
ITEM (2, 1, 2) |
|||
RECORD (2, 2) |
ITEM (2, 2, 1) |
||
ITEM (2, 2, 2) |
Figure 3: Schematic representation of TABLE
Initial values of table elements
A VALUE clause must not appear in a record description entry with an OCCURS clause, or in any record description entry subordinate to that entry. However, for the definition of condition-names, the VALUE clause is allowed and required here as well.
Initial values may be assigned to a table in the WORKING-STORAGE SECTION or LOCAL-STORAGE SECTION by using the VALUE clause.
Example 2-16
WORKING-STORAGE SECTION. ****** 1. VALUE ON GROUP-LEVEL ****** 01 WOCHE VALUE "MONTAG DIENSTAG MITTWOCH DONNERSTAG "FREITAG SAMSTAG SONNTAG ". 02 TAG PIC X(10) OCCURS 7 TIMES. ****** 2. REPEATED VALUE WITH OCCURS ****** 01 WEEK. 02 WDAY PIC X(10) OCCURS 7 TIMES VALUE FROM (1) "MONDAY" "TUESDAY" "WEDNESDAY" "THURSDAY" "FRIDAY" "SATURDAY" "SUNDAY". ****** 3. REPEATED VALUE SUBORDINATE TO OCCURS ****** 01 UGE. 02 FILLER OCCURS 7 TIMES. 03 DAG PIC X(10) VALUE FROM (1) "MANDAG" "TISDAG" "ONSDAG" "TORSDAG" "FREDAG" "LOERDAG" "SOENDAG".
References to table elements
All the elements within a table have the same data-name. To identify individual occurrences of table elements, occurrence numbers (indexes) enclosed in parentheses are appended to the data-name.
Example 2-17
01 TABLE4. 02 ELEMENT OCCURS 10 TIMES. . . . MOVE ELEMENT OF TABLE4 (8) TO ...
Here the eighth table element is accessed.
An occurrence number must be supplied for each dimension.
There are two techniques for referencing table elements:
subscripting
indexing