SET Statement
SET Statement Example
Initializing & Incrementing the table indexes
Scenario - Declaring an index, initialized, incremented and used to navigate the table.
Code -
----+----1----+----2----+----3----+----4----+----5----+
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.
Output -
STUDENT - 001PAWAN Y STUDENT - 002KUMAR
Explaining Example -
In the above example:
- It defines a table WS-CLASS with an index WS-IDX, consisting of student records with roll numbers and names.
- It then initializes the index to 1 and assigns values to the table entries using the index.
- After incrementing the index, it displays the entire table by iterating over the index using a PERFORM loop, displaying each student's information.
Setting the condition name to true or false -
Scenario - Condition names declaration (all formats) using 88 level number.
Code -
----+----1----+----2----+----3----+----4----+----5----+
IDENTIFICATION DIVISION.
PROGRAM-ID. LEVEL88S.
AUTHOR. MTH.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-ALPHABET PIC X(01).
* Condition names with single values
88 ALPHABET-A VALUE "A".
88 ALPHABET-S VALUE "S".
* Condition names with multiple values
88 VALID-ALPHABET VALUE "A" THROUGH "Z".
88 VOWELS VALUE "A" "E" "I" "O" "U".
* Condition names with range of values
88 CONSONANTS VALUE "B" THRU "D"
"F" THRU "H"
"J" THRU "N"
"P" THRU "T"
"V" THRU "Z".
PROCEDURE DIVISION.
SET ALPHABET-A TO TRUE.
IF VOWELS
DISPLAY "ALPHABET IS VOWEL: " WS-ALPHABET
END-IF.
SET ALPHABET-S TO TRUE.
IF CONSONANTS
DISPLAY "ALPHABET IS CONSONENT: " WS-ALPHABET
END-IF.
STOP RUN.
Output -
ALPHABET IS VOWEL: A ALPHABET IS CONSONENT: S
Explaining Example -
In the above example:
- WS-ALPHABET is declared as a single-byte alphanumeric variable. It has five condition names.
- ALPHABET-A and ALPHABET-S are single-value condition names. VOWELS is a multiple-value condition name. VALID-ALPHABET CONSONANTS is a condition name with a set of values.