Table Processing


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.

Below list of topics we are going to discuss in this chapter -

  • Table Declaration
  • Subscript
  • Index
  • SET Statement
  • Search
  • Search all

Table Declaration -


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

01 table-name.
   02 variable    [PIC data-type(length1)] 
                  OCCURS integer1 TIMES
                  [INDEXED BY index-name]
    ...
  • table-name - specifies the table name.
  • variable - specifies the data item name.
  • integer1 - The number of times the data item should be repeated.
  • INDEXED BY index-name - This defines an index for the table. The index can be used to reference specific occurrences within the table.

Single Dimensional Table –

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

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

       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.

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

       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

Subscript


Table data can be accessed by using subscript. Subscript represents the number of table occurrences. It is automatically created with the OCCURS clause. But, it needs a separate WORKING-STORAGE variable that should delcare as S9(04) COMP.

Example - Let us declare a table to store two student details. WS-STUDENT is variable with all student information OCCURS 2 times to capture the two students information. Declaring a subscript, initialized, incremented and used to display the student information.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TBSUBSCR.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-CLASS.
          03 WS-STUDENT  OCCURS 2 TIMES. 
             05 WS-ROLL-NO      PIC X(03). 
             05 WS-NAME         PIC X(10). 
	  * Declaring a subscript
       01 WS-SUB                PIC S9(04) COMP. 

       PROCEDURE DIVISION. 
      * Initializing the subscript to 1 
           MOVE 1               TO WS-SUB. 
           MOVE "001PAWAN Y"    TO WS-STUDENT (WS-SUB).

      * Incrementing subscript by 1
           COMPUTE WS-SUB = WS-SUB + 1. 
           MOVE "002KUMAR"      TO WS-STUDENT (WS-SUB).

      * Displaying full table using subscript
           PERFORM VARYING WS-SUB FROM 1 BY 1 UNTIL WS-SUB > 2 
                   DISPLAY "STUDENT" WS-SUB " - " WS-STUDENT(WS-SUB)
           END-PERFORM.
           STOP RUN.

JCL to execute the above COBOL program −

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

Output -

STUDENT0001 - 001PAWAN Y 
STUDENT0002 - 002KUMAR 

Index


Table data can be accessed by using index. Index refers the table element as the number of displacement positions from the table starting position. It is always declared with table and initialized, increment or decrement by SET statement. We will disucss SET statement at the end of this chapter.

Example - Let us declare a table to store two student details. WS-STUDENT is variable with all student information OCCURS 2 times to capture the two students information. Declaring an index, initialized, incremented and used to display the student information.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TBINDEX.

       DATA DIVISION. 
       WORKING-STORAGE SECTION.
	  * Declaring table with index
       01 WS-CLASS.
          03 WS-STUDENT  OCCURS 2 TIMES INDEXED BY WS-IDX.
             05 WS-ROLL-NO      PIC X(03).
             05 WS-NAME         PIC X(10).

       PROCEDURE DIVISION.
      * Initializing index to 1 
		   SET WS-IDX          TO 1.
		   MOVE "001PAWAN Y"   TO WS-STUDENT(WS-IDX).

      * Incrementing index by 1
		   SET WS-IDX          UP BY 1.
		   MOVE "002KUMAR"     TO WS-STUDENT(WS-IDX).

      * Displaying full table using index
           PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 2  
                   DISPLAY "STUDENT - " WS-STUDENT(WS-IDX)
           END-PERFORM.
           STOP RUN.

JCL to execute the above COBOL program −

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

Output -

STUDENT0001 - 001PAWAN Y 
STUDENT0002 - 002KUMAR 

SET Statement


The SET statement is used to initialize the table indexes and increasing or decreasing table indexes.

Initializing the table indexes - WS-INDEX is initialized with value 1.

SET WS-INDEX      TO 1

Increasing index - WS-INDEX value is increased by 1.

SET WS-INDEX    UP BY 1

Decreasing index - WS-INDEX value is decreased by 1.

SET WS-INDEX    DOWN BY 1

SEARCH


The SEARCH is used to perform a linear search on the table (also known as an array) for a specific item. It works with tables that have the OCCURS clause and are INDEXED BY an index. This SEARCH is called sequential search, serial search, linear search, or simple search.

SEARCH table-name
         VARYING index-name
    [AT END statement-block-1]
    WHEN relational-condition
        statement-block-2
	    ...
[END-SEARCH].

Example - Let us assume we have a employee table for an organization with all active employee numbers (unsorted) and we are trying to searching for exmployee E0004 existance. If the employee found, we should display "Employee found". Otherwise, display "Employee not found".

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TBSEARCH.
       AUTHOR. MTH.
	   
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-ORG.
          03 WS-EMPLOYEE OCCURS 6 TIMES 
                         INDEXED BY IDX-EMP.   
             05 WS-EMPLOYEE-NUM       PIC X(05).   

       PROCEDURE DIVISION.
      * Initializing table with active employee details
      * every 5 characters represents one employee number.
           MOVE 'E0005E0002E0004E0001E0007'
  		     TO WS-ORG.
      * Initializing index
           SET IDX-EMP         TO 1.
      * Search table using index
           SEARCH WS-EMPLOYEE VARYING IDX-EMP 
               AT END DISPLAY "Employee not found"
             WHEN WS-EMPLOYEE-NUM(IDX-EMP) = 'E0004'
                  DISPLAY "Employee found"
           END-SEARCH.

           STOP RUN.

JCL to execute the above COBOL program −

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

Output -

Employee found

SEARCH ALL


The SEARCH ALL statement is used to perform binary search on tables (or arrays). It is more efficient for large tables, provided that the table should be in sorted order (either ascending or descending) before the binary search (SEARCH ALL) applies.

SEARCH ALL table-name
    [AT END statement-block-1]
    WHEN relational-condition
        statement-block-2|NEXT SENTENCE
	    ...
[END-SEARCH]

Example - Let us assume we have a employee table for an organization with all active employee numbers (sorted) and we are trying to searching for exmployee E0004 existance. If the employee found, we should display "Employee found". Otherwise, display "Employee not found".

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TBSRCHAL.
       AUTHOR. MTH.
	   
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-ORG.
          03 WS-EMPLOYEE OCCURS 6 TIMES 
                         INDEXED BY IDX-EMP.   
             05 WS-EMPLOYEE-NUM       PIC X(05).   

       PROCEDURE DIVISION.
      * Initializing table with active employee details
      * every 5 characters represents one employee number.
           MOVE 'E0001E0002E0004E0005E0007'
  		     TO WS-ORG.
      * Initializing index
           SET IDX-EMP         TO 1.
      * Search table using index
           SEARCH ALL WS-EMPLOYEE
               AT END DISPLAY "Employee not found"
             WHEN WS-EMPLOYEE-NUM(IDX-EMP) = 'E0004'
                  DISPLAY "Employee found"
           END-SEARCH.

           STOP RUN.

JCL to execute the above COBOL program −

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

Output -

Employee found