Summary -
In this topic, we described about the Renames Clause with detailed example.
RENAMES used to regroup the elementary items of a group item. RENAMES creates an alternative logical group from the group of elementary items. Special purpose level number 66 is used to specify the RENAMES clause.
Syntax -

In the above syntax,
- data-name-t - Specifies alternative name for the logical group.
- data-name-1 - Specifies a starting elementary item.
- data-name-n - Specifies ending elementary data item in the basic group.
When data-name-n is not specified, the data-name-1 must be a group item and all the elementary items under data-item-1 RENAMED to data-name-t.
For example -
02 WS-VAR1. 05 WS-A ... 05 WS-B ... 05 WS-C ... 05 WS-D ... 05 WS-E ... 05 WS-F ... 66 WS-VAR2 RENAMES WS-VAR1.
data-name-t -
Specifies an alternative grouping name of data items.
For example - WS-VAR2 is the alternative grouping name for WS-A, WS-B...
02 WS-VAR1. 05 WS-A ... 05 WS-B ... 05 WS-C ... 66 WS-VAR2 RENAMES WS-VAR1.
data-name-t cannot be used as a qualifier.
data-name-1, data-name-n -
Specifies the starting and ending elementary data items. They are elementary or group items within the level-01 entry. data-name-1 and data-name-n can be an elementary data item or an alphanumeric group item.
For example - WS-A and WS-B are the starting and ending elementary items under WS-VAR2.
02 WS-VAR1. 05 WS-A ... 05 WS-B ... 05 WS-C ... 66 WS-VAR2 RENAMES WS-A THROUGH WS-B.
Rules -
- RENAMES entries must be in a sequential order.
For example - Valid declaration02 WS-VAR1. 05 WS-A ... 05 WS-B ... 05 WS-C ... 05 WS-D ... 05 WS-E ... 05 WS-F ... 66 WS-VAR2 RENAMES WS-A THROUGH WS-E.
Invalid declaration02 WS-VAR1. 05 WS-A ... 05 WS-B ... 05 WS-C ... 05 WS-D ... 05 WS-E ... 05 WS-F ... 66 WS-VAR2 RENAMES WS-E THROUGH WS-A.
- 66 level numbers didn’t have a PIC clause.
For example -02 WS-VAR1. 05 WS-A PIC X(5). 05 WS-B PIC X(5). 05 WS-C PIC X(5). 05 WS-D PIC X(5). 05 WS-E PIC X(5). 05 WS-F PIC X(5). 66 WS-VAR2 RENAMES WS-A THROUGH WS-E.
- RENAMES clause must be coded at the end of the group.
For example - Valid declaration02 WS-VAR1. 05 WS-A PIC X(5). 05 WS-B PIC X(5). 05 WS-C PIC X(5). 05 WS-D PIC X(5). 05 WS-E PIC X(5). 05 WS-F PIC X(5). 66 WS-VAR2 RENAMES WS-A THROUGH WS-E.
Invalid declaration02 WS-VAR1. 05 WS-A PIC X(5). 05 WS-B PIC X(5). 05 WS-C PIC X(5). 05 WS-D PIC X(5). 05 WS-E PIC X(5). 66 WS-VAR2 RENAMES WS-A THROUGH WS-E. 05 WS-F PIC X(5).
- Level-66 entry cannot rename level-01, level-77, level-88, or another level-66 entry.
- Elementary items with OCCURS or OCCURS DEPENDING ON clause should not be RENAMED.
All RENAMES entries associated with logical record must immediately follow that record's last elementary item declaration. that is, 66 level number must be declared immediately after the last elementary declaration of 01 level number.
For example -02 WS-VAR1. 05 WS-A PIC X(10). 05 WS-B PIC X(10). 66 WS-VAR2 RENAMES WS-VAR1.
When the THROUGH phrase is not specified, the storage area occupied by data-name-1 becomes the storage area occupied by data-name-t and all of the data attributes of data-name-1 become the data attributes for data-name-t.
For example -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 item A is declared with 5 items from ITEM1 to ITEM5 stored on continuous memory locations. B is defined as renaming of A without THROUGH.
Here B is just a renaming variable for the data in the variable A and uses the same memory location used by A. Below diagram can explains about how A and B represents in memory -

When the THROUGH phrase is specified, data-name-t defines an alphanumeric group item that includes all the elementary items that start with data-name-1 and end with data-name-n. The storage area occupied by the starting item through the ending item becomes the storage area occupied by data-name-t.
For example -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 item A is declared with 10 items from ITEM1 to ITEM10 stored on continuous memory locations. B is defined as renaming of A with 6 items 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. Below diagram can explains about how A and B represents in memory -

Practical Example -
Scenario - Below example describes how the 66 level number used in COBOL programming.
Code -

----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
IDENTIFICATION DIVISION.
PROGRAM-ID. RENAME.
AUTHOR. MAINFRAMESTECHELP.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-VAR.
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".
66 WS-GRP-ITEM2 RENAMES WS-VAR1 THROUGH WS-VAR2.
01 WS-VAR2.
02 WS-GRP-ITEM3.
05 WS-VAR31 PIC X(10) VALUE "MAINFRAMES".
05 FILLER PIC X(01).
05 WS-VAR32 PIC X(03) VALUE "ARE".
05 FILLER PIC X(01).
05 WS-VAR33 PIC X(10) VALUE "LEGENDARY".
05 FILLER PIC X(01).
05 WS-VAR34 PIC X(10) VALUE "SYSTEMS".
66 WS-GRP-ITEM4 RENAMES WS-GRP-ITEM3.
PROCEDURE DIVISION.
DISPLAY "GROUP ITEM1: " WS-GRP-ITEM1.
DISPLAY "GROUP ITEM2: " WS-GRP-ITEM2.
DISPLAY "GROUP ITEM3: " WS-GRP-ITEM3.
DISPLAY "GROUP ITEM4: " WS-GRP-ITEM4.
STOP RUN.
**************************** Bottom of Data ****************************
Output -

Explaining Example -
In the above example, WS-GRP-ITEM1 is a group item with multiple variables. WS-GRP-ITEM2 is defined as renaming of WS-GRP-ITEM1 from WS-VAR1 THROUGH WS-VAR2. So WS-GRP-ITEM2 displays the data from WS-VAR1 to WS-VAR2.
WS-GRP-ITEM4 defined as renaming the entire group item WS-GRP-ITEM3. So WS-GRP-ITEM4 displays the data same as WS-GRP-ITEM3 displays.