COBOL Redefining Variable with Different Length Example
Scenario - Redefining a variable with different lengths in COBOL programming.
Code -
----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. REDEFDIF.
       AUTHOR. MTH. 
       DATA DIVISION.
       WORKING-STORAGE SECTION. 
       01 WS-VAR. 
          05 WS-VAR1                       PIC X(20). 
      * Redefining variable with smaller length
          05 WS-RLE-VAR2 REDEFINES WS-VAR1 PIC X(10). 
      * Redefining variable with bigger length
          05 WS-RGT-VAR3 REDEFINES WS-VAR1 PIC X(30). 
       PROCEDURE DIVISION.
           MOVE "Mainframe technology"     TO WS-VAR1.
           DISPLAY "WS-VAR1:       " WS-VAR1.
           DISPLAY "WS-RLE-VAR2:   " WS-RLE-VAR2.
           DISPLAY "WS-RGT-VAR3:   " WS-RGT-VAR3.
           DISPLAY " ".
           MOVE "Mainframe Application system" TO WS-RGT-VAR3.
           DISPLAY "WS-VAR1:       " WS-VAR1.
           DISPLAY "WS-RLE-VAR2:   " WS-RLE-VAR2.
           DISPLAY "WS-RGT-VAR3:   " WS-RGT-VAR3.
           STOP RUN.Output -
WS-VAR1: Mainframe technology WS-RLE-VAR2: Mainframe WS-RGT-VAR3: Mainframe technology WS-VAR1: Mainframe Applicatio WS-RLE-VAR2: Mainframe WS-RGT-VAR3: Mainframe Application system
Explaining Example -
In the above example:
- WS-VAR1 is the source variable. WS-RLE-VAR2, and WS-RGT-VAR3 are the target variables on WS-VAR1.
- WS-RLE-VAR2 redefines WS-VAR1 with a length of 10 that is less than WS-VAR1 length. So, WS-RLE-VAR2 has the first 10 bytes of WS-VAR data.
- WS-RGT-VAR3 redefines WS-VAR1 of length 30, which is greater than WS-VAR1 length. So WS-RGT-VAR3 has the WS-VAR1 data plus another 10 bytes.
- Initially, WS-VAR1 was assigned with "MAINFRAME TECHNOLOGY" and the redefined variables WS-RLE-VAR2, and WS-RGT-VAR3 also had the same data according to their defined lengths.
- Later, the "MAINFRAME APPLICATION SYSTEM" was assigned to WS-RGT-VAR3. WS-VAR1, WS-RLE-VAR2, and WS-RGT-VAR3 also have the same data according to their defined lengths.
