Three Dimensional Array Example


Scenario - Three dimensional array.

Requirement - Let us declare a table to store two class details with two student details with 6 subjects marks. WS-CLASS is variable with all class information OCCURS 2 times to capture the two classes information. 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----+
      * Three Dimentional Table
       IDENTIFICATION DIVISION.
       PROGRAM-ID. THRDIMTB.
       AUTHOR. MTH.

       DATA DIVISION. 
       WORKING-STORAGE SECTION.
       01 WS-SCHOOL.
          02 WS-CLASS  OCCURS 2 TIMES.
             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. 

       PROCEDURE DIVISION.

      *    Populating class1 student1 details 
           MOVE "011"              TO WS-ROLL-NO(1,1)
           MOVE "PAWAN Y"          TO WS-NAME(1,1)
      *    Populating class1 student1 marks details (3rd dimension)		   
		   MOVE 079                TO WS-MARKS(1,1,1)
		   MOVE 077                TO WS-MARKS(1,1,2)
		   MOVE 082                TO WS-MARKS(1,1,3)
		   MOVE 076                TO WS-MARKS(1,1,4)
		   MOVE 089                TO WS-MARKS(1,1,5)
		   MOVE 092                TO WS-MARKS(1,1,6).
		   
      *    Populating class1 student2 details 		   
           MOVE "012"              TO WS-ROLL-NO(1,2)
           MOVE "KUMAR Y"          TO WS-NAME(1,2)
		   MOVE 083                TO WS-MARKS(1,2,1)
		   MOVE 079                TO WS-MARKS(1,2,2)
		   MOVE 078                TO WS-MARKS(1,2,3)
		   MOVE 089                TO WS-MARKS(1,2,4)
		   MOVE 093                TO WS-MARKS(1,2,5)
		   MOVE 086                TO WS-MARKS(1,2,6).

      *    Populating class2 student1 details 
           MOVE "021"              TO WS-ROLL-NO(2,1)
           MOVE "SRINIVAS"         TO WS-NAME(2,1)
           MOVE 079077082076089092 TO WS-MARKS-GRP(2,1).
      *    Populating class2 student2 details
           MOVE "022"              TO WS-ROLL-NO(2,2)
           MOVE "SRIDHAR"          TO WS-NAME(2,2)
           MOVE 083079078089093086 TO WS-MARKS-GRP(2,2).

           DISPLAY "Class1 Info: " WS-CLASS(1).
           DISPLAY " "
           DISPLAY "Class2 Info: " WS-CLASS(2).
           DISPLAY " "

           DISPLAY "Class1 Student1 Info   => " WS-STUDENT(1,1)
           DISPLAY " "
           DISPLAY "Class1 Student2 Info  => " WS-STUDENT(1,2)
           DISPLAY " "

           DISPLAY "Class2 Student1 Info   => " WS-STUDENT(2,1)
           DISPLAY " ".
           DISPLAY "Class2 Student2 Info  => " WS-STUDENT(2,2).

           STOP RUN.

JCL to execute the above COBOL program −

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

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

Class1 Info: 011PAWAN Y   079077082076089092012KUMAR Y   083079078089093086

Class2 Info: 021SRINIVAS  079077082076089092022SRIDHAR   083079078089093086

Class1 Student1 Info   => 011PAWAN Y   079077082076089092

Class1 Student2 Info  => 012KUMAR Y   083079078089093086 

Class2 Student1 Info   => 021SRINIVAS  079077082076089092

Class2 Student2 Info  => 022SRIDHAR   083079078089093086

Explaining Example -

In the above example:

  • WS-CLASS(1) represents class1 information and WS-CLASS(2) represents class2 information.
  • WS-STUDENT is the second dimension in the WS-CLASS array. WS-STUDENT(1,1) represents class1 first student information and WS-STUDENT(1,2) represents class1 second student information and so on.
  • WS-ROLL-NO(1,1), WS-NAME(1,1), WS-MARKS-GRP(1,1) represents class1 first student roll number, name and marks. similarly, WS-ROLL-NO(1,2), WS-NAME(1,2), WS-MARKS-GRP(1,2) represents class1 second student roll number, name, marks and so on.
  • WS-MARKS is the third dimension in the array WS-CLASS. WS-MARKS(1,1,1) represents class1 first student subject1 marks, WS-MARKS(1,1,2) represents class1 first student subject2 marks and so on.
  • WS-CLASS(1) represents the class1 informaton. i.e., two students information - WS-STUDENT(1,1), WS-STUDENT(1,2) and so on.