Data References


We should declare each variable only once in the program. However, the same variable name is used multiple times under different group variables. In this case, the variable name must be qualified to ensure the uniqueness of the reference. IN and OF are used for reference, and both are logically equivalent.

For example - Assume the same elementary variables are declared under two group variables. Referring to elementary variables should be like below -

----+----1----+----2----+----3----+----4----+----5----+
        ...
        WORKING-STORAGE SECTION.
		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).	
        ...
        PROCEDURE DIVISION.		   
           ...
           DISPLAY WS-ITEM1 OF WS-GROUP1.
           MOVE WS-ITEM1 IN WS-GROUP1
             TO WS-ITEM2 IN WS-GROUP2.
           ... 

If the references are not used for the above case (i.e., WS-ITEM1 is coded without IN), then the system throws the follwing 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.

Rules to Remember -

  • Data references are not used for individual variables.
  • Data references refer to the elementary variables uniquely defined under different groups.
  • The data name associated with the highest level must be unique in the hierarchy and the program.

Variable references -


Elementary variables under different group variables can have the same names. In this case, we should use referencing with their group variable to make them unique.

Syntax -

 elementary-variable IN|OF group-variable

Example -

Scenario1 - Describes how the references used for data division names in COBOL programming.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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.
		   ...

Output -

WS-GROUP1.WS-VAR1: MAINFRAMES
WS-GROUP2.WS-VAR1: MAINFRAMES

Condition name references -


Condition names under different variables can have the same names. In this case, we should reference the condition names with their variable names to make them unique.

Syntax -

 condition-name IN|OF variable

Example -

Scenario2 - Below example describes how the references used for condition names in COBOL programming.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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.
           ...

Output -

PERSON IS MALE

Paragraph references -


Paragraphs under different sections can have the same names. In this case, we should reference paragraphs with their section names to make them unique.

Syntax -

 paragraph-name IN|OF section-name

Example -

Scenario3 - Below example describes how the references used for procedure division names in COBOL programming.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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.

Output -

PERSON IS MALE

Copybook references -


Two files can have the same record structure, which should be declared for both. In this case, we should make variables unique by referencing their record names.

Syntax -

 variable-name IN|OF record-name

Example - Using same copybook for two different files.

Copybook -

Code -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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.
		   ...

Output -