66 Level Number
- Special purpose level number 66 is used to rename a group and assign a new name to it.
- It creates another logical group by re-grouping some or all elementary variables of a group.
- The RENAMES clause and 66-level numbers are used to rename a group.
- It provides a flexible way to access and manipulate data.
Syntax -
----+----1----+----2----+----3----+----4----+----5----+
01 WS-VAR-GRP1.
05 WS-VAR-A PIC ...
05 WS-VAR-B PIC ...
.
.
05 WS-VAR-N PIC ...
05 WS-VAR-O PIC ...
.
.
05 WS-VAR-Z PIC ...
* Renaming entire group
66 WS-VAR-GRP2 RENAMES VAR-A THRU VAR-N.
* Renaming some elementary variables
66 WS-VAR-GRP3 RENAMES WS-VAR-GRP1.
In the above syntax,
- WS-VAR-GRP1 - Specifies source group.
- WS-VAR-A THRU WS-VAR-N - Specifies starting and ending elementary variables that will be part of the new group.
- WS-VAR-GRP2, WS-VAR-GRP3 - Specifies target groups.
Points to note -
- THRU or THROUGH keyword is used when renaming some elementary variables (not all).
- THRU or THROUGH are ignored when renaming the entire group.
- The source group name is used to rename the whole group.
Rules to Remember -
- Renaming elementary variables should be in sequential order.
- 66 level number shouldn't have a PIC or PICTURE clause.
- The RENAMES clause should follow the target variable in the declaration.
- Level-01, level-77, level-88, or other level-66 entries can't be renamed.
- Elementary variables that are declared with the OCCURS clause should not be renamed.
Explaining in detail -
Scenario1 - Renaming the entire group.
The declaration of the existing group and renaming of the group are as follows -
02 A.
05 ITEM1 PIC X(5).
05 ITEM2 PIC X(5).
05 ITEM3 PIC X(5).
05 ITEM4 PIC X(5).
05 ITEM5 PIC X(5).
66 B RENAMES A.
In the above example, group variable A is declared with five elementary variables from ITEM1 to ITEM5. B is defined as the renaming of A without the THROUGH clause. Here, B is just a renaming variable for the data in variable A and uses the same memory location used by A.
The below diagram can explain how A and B represent memory -
Scenario2 - Renaming some elementary variables under a group.
The declaration of the existing group and renaming of some elementary variables are as follows -
02 A.
05 ITEM1 PIC X(5).
05 ITEM2 PIC X(5).
05 ITEM3 PIC X(5).
05 ITEM4 PIC X(5).
05 ITEM5 PIC X(5).
05 ITEM6 PIC X(5).
05 ITEM7 PIC X(5).
05 ITEM8 PIC X(5).
05 ITEM8 PIC X(5).
05 ITEM10 PIC X(5).
66 B RENAMES ITEM1 THRU ITEM6.
In the above example, group variable A is declared with ten elementary variables from ITEM1 to ITEM10. B is defined as the renaming of A with six elementary variables from ITEM1 to ITEM6. Here, B is just a renaming variable for the data from ITEM1 to ITEM6 and uses the same memory location used by A.
The below diagram can explain how A and B represent memory -
Practical Example -
Scenario - Renaming a group with some elementary variable in it.
Code -
----+----1----+----2----+----3----+----4----+----5----+
...
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-VARIABLE.
02 WS-GRP-ITEM1.
05 WS-VAR1 PIC X(10) VALUE "MAINFRAMES".
05 FILLER PIC X(01).
05 WS-VAR2 PIC X(08) VALUE "ARE VAST".
05 FILLER PIC X(01).
05 WS-VAR3 PIC X(01) VALUE "&".
05 FILLER PIC X(01).
05 WS-VAR4 PIC X(10) VALUE "LEGENDARY".
05 FILLER PIC X(01).
05 WS-VAR5 PIC X(10) VALUE "SYSTEMS".
* Renaming WS-GRP-ITEM1
66 WS-GRP-ITEM2 RENAMES WS-VAR1 THROUGH WS-VAR2.
...
PROCEDURE DIVISION.
DISPLAY "GROUP ITEM1: " WS-GRP-ITEM1.
DISPLAY "GROUP ITEM2: " WS-GRP-ITEM2.
...
Output -
GROUP ITEM1: MAINFRAMES ARE VAST & LEGENDARY SYSTEMS GROUP ITEM2: MAINFRAMES ARE VAST