Two Dimensional Array with Subscript Example


Scenario - Accessing two dimensional array with Subscript.

Requirement - 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----+
      * Accessing Two Dimentional Table using subscript
       IDENTIFICATION DIVISION.
       PROGRAM-ID. TWODIMTB.
       AUTHOR. MTH.

       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). 
             05 WS-MARKS-GRP.
                10 WS-MARKS     PIC 9(03) OCCURS 6 TIMES.
       01 WS-VAR.
	      03 WS-SUBSCR1         PIC S9(04) COMP.
		  03 WS-SUBSCR2         PIC S9(04) COMP.

       PROCEDURE DIVISION. 

      *    Populating student1 details (1st Dimension)
           MOVE "001"        TO WS-ROLL-NO(1)
           MOVE "PAWAN Y"    TO WS-NAME(1)
      *    Populating student1 marks (2nd Dimension)
		   MOVE 079          TO WS-MARKS(1,1)
		   MOVE 077          TO WS-MARKS(1,2)
		   MOVE 082          TO WS-MARKS(1,3)
		   MOVE 076          TO WS-MARKS(1,4)
		   MOVE 089          TO WS-MARKS(1,5)
		   MOVE 092          TO WS-MARKS(1,6). 

      *    Populating student2 details (1st Dimension)
           MOVE "002"        TO WS-ROLL-NO(2)
           MOVE "KUMAR Y"    TO WS-NAME(2)
      *    Populating student2 marks (2nd Dimension)
		   MOVE 083          TO WS-MARKS(2,1)
		   MOVE 079          TO WS-MARKS(2,2)
		   MOVE 078          TO WS-MARKS(2,3)
		   MOVE 089          TO WS-MARKS(2,4)
		   MOVE 093          TO WS-MARKS(2,5)
		   MOVE 086          TO WS-MARKS(2,6).

           DISPLAY "Class Info: " WS-CLASS.
           DISPLAY " "

      *    Initializing first dimension subscript
           MOVE 1            TO WS-SUBSCR1.
           DISPLAY "Students Information   => " 

      *    Loop for displaying 2 students information
           PERFORM UNTIL WS-SUBSCR1 > 2
               DISPLAY "Roll No:  " WS-ROLL-NO (WS-SUBSCR1)
               DISPLAY "Name:     " WS-NAME (WS-SUBSCR1)

      *        Initializing second dimension subscript
               MOVE 1        TO WS-SUBSCR2

      *        Loop for displaying 6 subjects information
               DISPLAY "MARKS:  "
               PERFORM UNTIL WS-SUBSCR2 > 6
      *        Accessing subject marks
                   DISPLAY WS-MARKS(WS-SUBSCR1, WS-SUBSCR2)

      *            Increasing the second dimension subscript by 1 
                   ADD 1      TO WS-SUBSCR2
               END-PERFORM

      *        Increasing the first dimension subscript by 1
               ADD 1      TO WS-SUBSCR1
           END-PERFORM.

           STOP RUN.

JCL to execute the above COBOL program −

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

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

Class Info: 001PAWAN Y   079077082076089092002KUMAR Y   083079078089093086

Students Information   =>
Roll No:  001
Name:     PAWAN Y
MARKS:
079
077
082
076
089
092
Roll No:  002
Name:     KUMAR Y
MARKS:
083
079
078
089
093
086

Explaining Example -

In the above example:

  • WS-STUDENT(1) represents first student information and WS-STUDENT(2) represents second student information.
  • WS-SUBSCR1 is subscript declared for WS-STUDENT 1st dimension array. The subscript is initialized using MOVE statement and incremented using ADD statement.
  • WS-ROLL-NO(1), WS-NAME(1), WS-MARKS-GRP(1) represents first student roll number, name and marks. similarly, WS-ROLL-NO(2), WS-NAME(2), WS-MARKS-GRP(2) represents second student roll number, name and marks.
  • WS-MARKS is the second dimension in the array WS-STUDENT. WS-MARKS(1,1) represents first student subject1 marks, WS-MARKS(1,2) represents first student subject2 marks and so on.
  • WS-SUBSCR2 is subscript declared for WS-MARKS 2nd dimension array.
  • WS-CLASS represents the full class informaton. i.e., two students information - WS-STUDENT(1) and WS-STUDENT(2).