Three Dimensional Array with Subscript
Three Dimensional Array with Subscript Example
Scenario - Accessing three dimensional array with subscript.
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----+
* Accessing Three Dimentional Table using subscript
IDENTIFICATION DIVISION.
PROGRAM-ID. THRDIMIX.
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.
01 WS-VAR.
02 WS-SUBSCR1 PIC S9(04) COMP.
02 WS-SUBSCR2 PIC S9(04) COMP.
02 WS-SUBSCR3 PIC S9(04) COMP.
PROCEDURE DIVISION.
MOVE "011" TO WS-ROLL-NO(1,1)
MOVE "PAWAN Y" TO WS-NAME(1,1)
MOVE 079077082076089092 TO WS-MARKS-GRP(1,1)
MOVE "012" TO WS-ROLL-NO(1,2)
MOVE "KUMAR Y" TO WS-NAME(1,2)
MOVE 083079078089093086 TO WS-MARKS-GRP(1,2)
MOVE "021" TO WS-ROLL-NO(2,1)
MOVE "SRINIVAS" TO WS-NAME(2,1)
MOVE 079077082076089092 TO WS-MARKS-GRP(2,1)
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 " "
* Initializing first dimension subscript
MOVE 1 TO WS-SUBSCR1.
DISPLAY "Students Information => "
* Loop for displaying 2 classes information
PERFORM UNTIL WS-SUBSCR1 > 2
* Initializing second dimension subscript
MOVE 1 TO WS-SUBSCR2
* Loop for displaying 2 classes information
PERFORM UNTIL WS-SUBSCR2 > 2
DISPLAY "Roll No: " WS-ROLL-NO (WS-SUBSCR1,WS-SUBSCR2)
DISPLAY "Name: " WS-NAME (WS-SUBSCR1,WS-SUBSCR2)
* Initializing 3rd dimension subscript
MOVE 1 TO WS-SUBSCR3
* Loop for displaying 6 subjects information
DISPLAY "MARKS: "
PERFORM UNTIL WS-SUBSCR3 > 6
* Accessing subject marks
DISPLAY WS-MARKS (WS-SUBSCR1,WS-SUBSCR2, WS-SUBSCR3)
* Increasing the 3rd dimension Index by 1
ADD 1 TO WS-SUBSCR3
END-PERFORM
* Increasing the 3rd dimension Index by 1
ADD 1 TO WS-SUBSCR2
END-PERFORM
* Increasing the first dimension Index 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=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 Students Information => Roll No: 011 Name: PAWAN Y MARKS: 079 077 082 076 089 092 Roll No: 012 Name: KUMAR Y MARKS: 083 079 078 089 093 086 Roll No: 021 Name: SRINIVAS MARKS: 079 077 082 076 089 092 Roll No: 022 Name: SRIDHAR MARKS: 083 079 078 089 093 086
Explaining Example -
In the above example:
- WS-CLASS(1) represents class1 information and WS-CLASS(2) represents class2 information.
- WS-SUBSCR1 is subscript declared on WS-CLASS 1st dimension array. The subscript is initialized using MOVE statement and incremented using ADD statement.
- 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-SUBSCR2 is subscript declared on WS-STUDENT 2nd dimension array.
- 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-SUBSCR3 is subscript declared on WS-MARKS 3rd dimension array.
- WS-CLASS(1) represents the class1 informaton. i.e., two students information - WS-STUDENT(1,1), WS-STUDENT(1,2) and so on.