COBOL Single Dimension Array with Index Example
Scenario - Accessing single dimensional array using index.
Requirement - Let us declare a table to process two student details. WS-CLASS is the group variable and WS-STUDENT is a variable with student information OCCURS 2 times to capture the two students information.
Code -
----+----1----+----2----+----3----+----4----+----5----+
      * Single Dimentional Table
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SINDIMIX.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
	  * Declaring the array with Index
       01 WS-CLASS.
          03 WS-STUDENT  OCCURS 2 TIMES INDEXED BY IDX-ONE.
             05 WS-ROLL-NO      PIC X(03).
             05 WS-NAME         PIC X(10).
       PROCEDURE DIVISION.
      *    Populating array occurrences
           MOVE "001PAWAN Y" TO WS-STUDENT(1).
           MOVE "002KUMAR Y" TO WS-STUDENT(2).
           DISPLAY "Class Information: " WS-CLASS.
           DISPLAY " "
      *    Initializing Index
           SET IDX-ONE        TO 1.
           DISPLAY "Students Information   => "
		   
	  *    Loop for displaying two students information
           PERFORM UNTIL IDX-ONE > 2
               DISPLAY "Roll No:  " WS-ROLL-NO (IDX-ONE)
               DISPLAY "Name:     " WS-NAME (IDX-ONE)
	  *	       Increasing the Index by 1
               SET IDX-ONE UP BY 1
           END-PERFORM.
           STOP RUN.JCL -
//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=SINDIMIX //STEPLIB DD DSN=MATEPK.COBOL.LOADLIB,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
Class Information: 001PAWAN Y 002KUMAR Y Students Information => Roll No: 001 Name: PAWAN Y Roll No: 002 Name: KUMAR Y
Explaining Example -
In the above example:
- WS-STUDENT(1) represents first student information and WS-STUDENT(2) represents second student information.
- IDX-ONE is index declared on WS-STUDENT single dimensional array. The index is initialized and incremented using SET statement.
- WS-ROLL-NO(1), WS-NAME(1) represents first student roll number and name. similarly, WS-ROLL-NO(2), WS-NAME(2) represents the second student roll number and name.
- WS-CLASS represents the full class informaton. i.e., two students information - WS-STUDENT(1) and WS-STUDENT(2).
