Data References
Every user-defined name names a resource for solving a data processing problem in a COBOL program. A user-defined name must contain a reference to uniquely identifies the resource.
A user-defined name can be qualified, subscripted, or reference modified to ensure uniqueness of reference. IN and OF are used for reference, and both are logically equivalent.
For example - Assume same elementary items declared under two group items. Referring elementary items should be like below -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
01 WS-GROUP1.
02 WS-ITEM1 PIC X(10).
02 WS-ITEM2 PIC X(10).
01 WS-GROUP2.
02 WS-ITEM1 PIC X(10).
02 WS-ITEM2 PIC X(10).
...
DISPLAY WS-ITEM1 OF WS-GROUP1.
MOVE WS-ITEM1 IN WS-GROUP1
TO WS-ITEM2 IN WS-GROUP2.
...
If the references not used for the above case(i.e., directly WS-ITEM1 referred), then system throws the below error -
"WS-ITEM1" was not a uniquely defined name. The definition to be used could not be determined from the context. The reference to the name was discarded.
Data references are not used for individual variables.
For example - Data references not valid for below -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
01 WS-VAR1 PIC X(15).
05 WS-VAR2 PIC X(04).
77 WS-VAR3 PIC X(10).
Data references are used only for the uniqueness of the same names/items declared under different hierarchies.
For example - Data references used for below -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
01 WS-GROUP1.
02 WS-ITEM1 PIC X(10).
02 WS-ITEM2 PIC X(10).
01 WS-GROUP2.
02 WS-ITEM1 PIC X(10).
02 WS-ITEM2 PIC X(10).
The data name associated with the highest level must be unique in any hierarchy and cannot be qualified.
For example - WS-GROUP1, WS-GROUP2 should be unique and should not be qualified in the above example.
Below are the references used according to the program structure –

Practical Example -
Scenario1 - Below example describes how the references used for data division names in COBOL programming.
Code -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
IDENTIFICATION DIVISION.
PROGRAM-ID. DREFDDN.
AUTHOR. MTH.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-GROUP1.
05 WS-VAR1 PIC X(10) VALUE 'MAINFRAMES'.
05 WS-VAR2 PIC 9(04) VALUE 2021.
01 WS-GROUP2.
05 WS-VAR1 PIC X(10).
05 WS-VAR2 PIC 9(04).
PROCEDURE DIVISION.
MOVE WS-VAR1 IN WS-GROUP1
TO WS-VAR1 IN WS-GROUP2.
DISPLAY "WS-GROUP1.WS-VAR1: " WS-VAR1 OF WS-GROUP1.
DISPLAY "WS-GROUP2.WS-VAR1: " WS-VAR1 OF WS-GROUP2.
STOP RUN.
**************************** Bottom of Data ****************************
Output -

Explaining Example -
- In the above example, WS-VAR1, WS-VAR2 are elementary items declared under group items WS-GROUP1, WS-GROUP2. WS-VAR1 is not unique and should have reference while using in the program. So, WS-VAR1 under WS-GROUP1 refers as WS-VAR1 OF WS-GROUP1 or WS-VAR1 IN WS-GROUP1. Similarly, refernces should specify for WS-VAR2.
Scenario2 - Below example describes how the references used for condition names in COBOL programming.
Code -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
IDENTIFICATION DIVISION.
PROGRAM-ID. DREFCN.
AUTHOR. MTH.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-GROUP1.
05 WS-GENDER PIC X(01).
88 MALE VALUE 'M'.
88 FEMALE VALUE 'F'.
01 WS-GROUP2.
05 WS-GENDER PIC X(01).
88 MALE VALUE 'M'.
88 FEMALE VALUE 'F'.
PROCEDURE DIVISION.
MOVE 'M' TO WS-GENDER OF WS-GROUP1.
IF MALE OF WS-GROUP1
DISPLAY 'PERSON IS MALE'
ELSE
DISPLAY 'PERSON IS FEMALE'
END-IF.
STOP RUN.
**************************** Bottom of Data ****************************
Output -

Explaining Example -
- In the above example, WS-GENDER is elementary item declared under group items WS-GROUP1, WS-GROUP2. WS-GENDER declared with condition names MALE and FEMALE. Those condition names are not unique and should have reference while using in the program. So, MALE condition name under WS-GROUP1 refers as MALE OF WS-GROUP1 or MALE IN WS-GROUP1. Similarly, refernces should specify for FEMALE condition name.
Scenario3 - Below example describes how the references used for procedure division names in COBOL programming.
Code -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
IDENTIFICATION DIVISION.
PROGRAM-ID. DREFPDN.
AUTHOR. MTH.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-GROUP1.
05 WS-GENDER PIC X(01).
88 MALE VALUE 'M'.
88 FEMALE VALUE 'F'.
PROCEDURE DIVISION.
MOVE 'M' TO WS-GENDER OF WS-GROUP1.
PERFORM PARAGRAPH1 OF SECTION1.
STOP RUN.
SECTION1 SECTION.
PARAGRAPH1.
IF MALE OF WS-GROUP1
DISPLAY 'PERSON IS MALE'
ELSE
DISPLAY 'PERSON IS FEMALE'
END-IF.
SECTION2 SECTION.
PARAGRAPH1.
IF MALE OF WS-GROUP1
DISPLAY 'PERSON IS MALE'
ELSE
DISPLAY 'PERSON IS FEMALE'
END-IF.
**************************** Bottom of Data ****************************
Output -

Explaining Example -
- In the above example, PARAGRAPH1 is a paragraph declared under section SECTION1, SECTION2. The paragraph PARAGRAPH1 is not unique and should have reference while using in the program. So, PARAGRAPH1 under SECTION1 refers as PARAGRAPH1 OF SECTION1 or PARAGRAPH1 IN SECTION1. Similarly, refernces should specify for PARAGRAPH1 under SECTION2.
Scenario4 - Below example describes how the references used for copy libraries in COBOL programming.
Copybook -

Code -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
IDENTIFICATION DIVISION.
PROGRAM-ID. DREFCL.
AUTHOR. MTH.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-STDREC1.
COPY STDREC.
01 WS-STDREC2.
COPY STDREC.
PROCEDURE DIVISION.
MOVE 1 TO STD-NO OF WS-STDREC1.
MOVE 'NAME1' TO STD-NAME OF WS-STDREC1.
MOVE 'MALE' TO STD-GENDER OF WS-STDREC1.
MOVE WS-STDREC1 TO WS-STDREC2.
DISPLAY 'WS-STDREC1: ' WS-STDREC1.
DISPLAY 'WS-STDREC2: ' WS-STDREC2.
STOP RUN.
**************************** Bottom of Data ****************************
Output -

Explaining Example -
- In the above example, STDREC is a copybook added under records WS-STDREC1, WS-STDREC2. STD-No, STD-NAME, STD-GENDER are the variables in the copybook STDREC. These variables are not unique and should have reference record name while using in the program. So, STD-NO under WS-STDREC1 refers as STD-NO OF WS-STDREC1 or STD-NO IN WS-STDREC1. Similarly, refernces should specify for STD-NAME and STD-GENDER.