Table | Array


COBOL arrays are also known as tables. Array is a collection of individual data items of same type and length. It is a linear data structure that uses to store the identical data repeated multiple times. For example - student marks for all subjects.

Declaration without using table concept to store 6 subject marks of a student as follows -

01 WS-STUDENT.
   03 WS-SUBJECT1-MARKS    PIC 9(03).
   03 WS-SUBJECT2-MARKS    PIC 9(03).
   03 WS-SUBJECT3-MARKS    PIC 9(03).
   03 WS-SUBJECT4-MARKS    PIC 9(03).
   03 WS-SUBJECT5-MARKS    PIC 9(03).
   03 WS-SUBJECT6-MARKS    PIC 9(03).

The repeated variables can be declared by using the OCCURS clause in COBOL. The above declaration with table concept is –

01 WS-STUDENT.
   03 WS-SUBJECT-MARKS  PIC 9(03) OCCURS 6 TIMES.

Table Declaration –


Tables are declared in the DATA DIVISION. OCCURS clause is used to declare the table in program. OCCURS clause specifies the number that represents how many times the data item is repeated in the table.

Syntax -

01 table-name.
   02 variable    [PIC data-type(length1)] 
                  OCCURS integer1 [TO integer2] TIMES
                  [DEPENDING ON data-name]
			      [DESCENDING|ASCENDING KEY IS key-var]
                  [INDEXED BY index-name]
    ...

Parameters -

  • table-name - specifies the table name.
  • variable - specifies the data item name.
  • integer1 - The number of times the data item should be repeated.
  • integer1 [TO integer2] - integer1 is minimum number of times and integer2 to maximum number of times. TO is applicable when DEPENDING ON is coded.
  • DEPENDING ON data-name - This makes the table variable-length, with its size determined by the current value of data-name.
  • DESCENDING|ASCENDING KEY IS key-var - Specifies the array sorting order using key-var.
  • INDEXED BY index-name - This defines an index for the table. The index can be used to reference specific occurrences within the table.

There are two parts in the table. i.e., first one is the table name and the second one is data item (variable). Table name is a group variable and should be declared with 01 level. Data item is an elementary variable that repeats in the table and should be declared with level numbers from 02 to 49. Data name always declared with PICTURE clause.

Rules -

  • Table name should not have OCCURS clause associated with it.
  • OCCURS and PICTURE clauses may not require to be together.
  • OCCURS clause should not be coded with level number of 01, 66, 77 or 88.
  • Each OCCURS clause is called as a dimension and up to 7 nested dimensions can be coded in a table.

Single Dimensional Table -


OCCURS clause is used only once to declare a single dimensional table.

Scenario - Let us declare a table to store two student details. WS-CLASS is the group variable and WS-STUDENT is a variable with all student information OCCURS 2 times to capture the two students information.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SINDIMTB.

       DATA DIVISION.
       WORKING-STORAGE SECTION. 
      * Single Dimensional table
       01 WS-CLASS.
          03 WS-STUDENT  OCCURS 2 TIMES.
             05 WS-ROLL-NO      PIC X(03) VALUE "001".
             05 WS-NAME         PIC X(10) VALUE "STUDENT1".

       PROCEDURE DIVISION. 
           DISPLAY "CLASS INFO: " WS-CLASS. 
           STOP RUN. 

JCL to execute the above COBOL program −

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID             
//*                                                      
//STEP01  EXEC PGM=SINDIMTB                              
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR         
//SYSOUT   DD  SYSOUT=*

When the program compiled and executed, it gives the following result −

CLASS INFO: 001STUDENT1  001STUDENT1  

Two Dimensional Table -


OCCURS clause is used within OCCURS to declare two-dimensional table.

Scenario - Let us declare a table to store two student details with 6 subjects marks. WS-STUDENT is variable with all student information OCCURS 2 times to capture the two students information. WS-MARKS-GRP is variable that OCCURS 6 times to capture 6 subjects marks.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. TWODIMTB.
 
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      * Two dimensional table
       01 WS-CLASS. 
          03 WS-STUDENT  OCCURS 2 TIMES.
             05 WS-ROLL-NO      PIC X(03) VALUE "001".
             05 WS-NAME         PIC X(10) VALUE "STUDENT1". 
             05 WS-MARKS-GRP    OCCURS 6 TIMES.
                10 WS-MARKS     PIC 9(03) VALUE 077.

       PROCEDURE DIVISION. 
           DISPLAY "CLASS INFO: " WS-CLASS. 
           STOP RUN. 

JCL to execute the above COBOL program −

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID             
//*                                                      
//STEP01  EXEC PGM=TWNDIMTB                              
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR         
//SYSOUT   DD  SYSOUT=*

When the program compiled and executed, it gives the following result −

CLASS INFO: 001STUDENT1  077077077077077077001STUDENT1  077077077077077077

How the table accessed in the program?


There are two ways to access the table in the program to process the data –

  • Subscript - Table elementary variables can be accessed by using subscript. Subscript is a number of occurrences of table.
  • Index - Table elementary variables can also be accessed by using index. Index is the number of displacement positions from the table starting.

How many types of tables?


COBOL supports two types of tables based on declaration –

  • Fixed-length tables - Specifies the number of OCCURS as a static value. If any changes needed to the number of OCCURS that requires a program modification.
  • Variable-length tables - Specifies the number of OCCURS decided dynamically using another variable. The number of OCCURS will be decided during the program run based on the variable value.