Memory Management Techniques


Memory management techniques refers to how programs allocate, use, and release memory during the program execution. This involves defining data structures in the DATA DIVISION and using storage areas in WORKING-STORAGE. Proper memory management ensures efficient program execution, minimizes wasted resources, and prevents memory-related errors.

Below are the list of memory management techniques available in COBOL -

  • REDEFINES
  • RENAMES
  • SYNCHRONIZED Clause
  • Computational Items (USAGE Clause)

REDEFINES


The REDEFINES allows one variable to share the same storage area as another variable. It is a way to declare multiple variables for a single storage area in different ways, depending on the requirement.

level-number target-variable REDEFINES source-variable [PIC ...].
  • level-number - The level number at which the variable is defined. It should be the same for both source and target variables.
  • target-variable - Name of the new variable that is going to share the storage of source-variable.
  • source-variable - Name of the variable whose storage is being redefined by target-variable.
  • PIC .. - Optional. Additional clauses that describe the data, like PIC, VALUE, etc.

Example - Redefining a variable with same and different lengths.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. REDEFINE.
       AUTHOR. MTH.
	   
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-VAR.
	      05 WS-VAR1                      PIC X(20). 
          05 WS-RLE-VAR2 REDEFINES WS-VAR PIC X(10).

       PROCEDURE DIVISION.
           MOVE "MAINFRAME TECHNOLOGY"     TO WS-VAR1.
           DISPLAY "WS-VAR1:        " WS-VAR1.
           DISPLAY "WS-RLE-VAR2:    " WS-RLE-VAR2.
           DISPLAY " ".

           MOVE "MAINFRAME APPLICATION SYSTEM" TO WS-RLE-VAR2.
           DISPLAY "WS-VAR1:        " WS-VAR1.
           DISPLAY "WS-RLE-VAR2:    " WS-RLE-VAR2.
           STOP RUN. 

JCL to execute the above COBOL program −

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID             
//*                                                      
//STEP01  EXEC PGM=REDEFINE                              
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR         
//SYSOUT   DD  SYSOUT=*

When the program compiled and executed, it gives the following result −

WS-VAR1:        MAINFRAME TECHNOLOGY
WS-RLE-VAR2:    MAINFRAME 

WS-VAR1:        MAINFRAME APPLICATIO
WS-RLE-VAR2:    MAINFRAME 

RENAMES


The RENAMES clause is used to define an alternative name to an existing group of items. It allows more flexible referencing of those items based on the requirement. Special purpose level number 66 is used to code the RENAMES clause.

       01 WS-VAR-GRP1.
          05 WS-VAR-A      PIC ... 
             . 
          05 WS-VAR-N      PIC ...
          05 WS-VAR-O      PIC ...
             . 
          05 WS-VAR-Z      PIC ...
       66 WS-VAR-GRP2      RENAMES VAR-A THRU VAR-N.
  • WS-VAR-GRP1 - Specifies source group variable.
  • WS-VAR-A, ..., WS-VAR-N - Specifies starting and ending elementary variables to be renamed.
  • WS-VAR-GRP2 - Specifies target variable.

Example - Variable declaration using 66-level number and the variable usage in PROCEDURE DIVISION.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. RENAME.
       AUTHOR. MTH.
 
       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".
      * 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.

           STOP RUN. 

JCL to execute the above COBOL program −

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID             
//*                                                      
//STEP01  EXEC PGM=RENAME                              
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR         
//SYSOUT   DD  SYSOUT=*

When the program compiled and executed, it gives the following result −

GROUP ITEM1: MAINFRAMES ARE VAST & LEGENDARY  SYSTEMS
GROUP ITEM2: MAINFRAMES ARE VAST

Explaining Example -

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

SYNCHRONIZED Clause


The SYNCHRONIZED clause is used to allocate the variables at their respective natural memory boundaries (immediately after the previous variable allocation ends) and removes the slack bytes.

data-item   PIC data-type(length) [SYNCHRONIZED [LEFT|RIGHT]]
  • data-item - Name of the data item being defined.
  • LEFT - Optional. It specifies left alignment and used for alphanumeric items.
  • RIGHT - Optional. It specifies right alignment and used for numeric items. If neither coded, RIGHT is the default.

Example - Explaining the concept with student record.

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
   05 STUDENT-NAME     PIC X(12).
   05 STUDENT-GRADE    PIC 9(02).
   05 STUDENT-CLASS    PIC X(03).

The compiler inserts the slack bytes after STUDENT-NO to start the next item STUDENT-NAME from the boundary. Similary, for the STUDENT-GRADER to start the STUDENT-CLASS from the boundary. The declaration becomes after slack bytes is -

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
  [05 SLACK-BYTES      PIC XX.  INSERTED BY COMPILER]
   05 STUDENT-NAME     PIC X(12).
   05 STUDENT-GRADE    PIC 9(02).
  [05 SLACK-BYTES      PIC XX.  INSERTED BY COMPILER]
   05 STUDENT-CLASS    PIC X(03).

Total 4 slack bytes inserted if we are not used SYNC clause. To avoid the slack bytes, the layout should be declared with SYNC clause like below -

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
   05 STUDENT-NAME     PIC X(12) SYNC.
   05 STUDENT-GRADE    PIC 9(02).
   05 STUDENT-CLASS    PIC X(03) SYNC.

The below diagram represents the same memory allocation along SYNC clause and there will be no slack bytes anymore -

Slack bytes within record

Computational Items (USAGE Clause)


Computational items refer to data items used for arithmetic calculations. These items are typically defined with the USAGE clause to specify their internal representation.

The list of USAGE modes in COBOL are -

  • DISPLAY
  • COMP | COMPUTATION
  • COMP-1 | COMPUTATION-1
  • COMP-2 | COMPUTATION-2
  • COMP-3 | COMPUTATION-3
  • COMP-4 | COMPUTATION-4
  • COMP-5 | COMPUTATION-5

DISPLAY Computation

DISPLAY computation uses the character form. In character form, one character equals one byte (8 bits) of storage. If no usage clause is used, then DISPLAY usage will be applied by default.

It applies to the Numeric, Alphabetic and Alphanumeric data types. For example -

01 WS-VAR.
   05 WS-VAR1          PIC 9(06) USAGE DISPLAY.
   05 WS-VAR2          PIC 9(06).

BINARY | COMP | COMPUTATION

COMP (BINARY) is used to store signed decimal numbers in pure binary format and applicable to numeric data items. This format is often used for arithmetic operations as it provides efficient storage and fast computation. The below table represents the storage occupied based on the number of digits in the PICTURE clause –

Digits in PICTURE clauseStorage occupied
1 through 42 bytes (halfword)
5 through 94 bytes (full word)
10 through 188 bytes (doubleword)
For example -

01 WS-VAR.
   05 WS-VAR1   PIC 9(5) USAGE IS COMP.
   05 WS-VAR2   PIC 9(8) COMP.

Both WS-VAR1 and WS-VAR2 occupies 4 bytes of memory.

COMP-1 | COMPUTATION-1

COMP-1 is used to store single-precision (32 bit) floating-point numbers and applicable to numeric data items. It has no PICTURE clause, which is 4 bytes long (FULL WORD). COMP-1 data is stored in the format of mantissa and exponent.

Digits in PICTURE clause Storage occupied
1 through 16 4 bytes (FULL WORD)
For example -

01 WS-VAR.
   05 WS-PI        USAGE IS COMP-1.
   05 WS-RADIUS    USAGE IS COMP-1.

COMP-2 | COMPUTATION-2

COMP-2 is a USAGE type used to store internal double-precision (64 bit) floating-point numbers and applicable to numeric data items. It has no PICTURE clause, and it is 8 bytes long (DOUBLE WORD). COMP-2 data is stored in the format of mantissa and exponent.

Digits in PICTURE clauseStorage occupied
1 through 328 bytes (DOUBLE WORD)
For example -

01 WS-VAR.
   05 WS-PI        USAGE IS COMP-2.
   05 WS-RADIUS    USAGE IS COMP-2.

COMP-3 | COMPUTATION-3

COMP-3 (or Packed Decimal or Packed Numeric) is used to represent decimal numbers in a compact binary-coded decimal (BCD) format and applicable to numeric data items. COMP-3 variable contains any of the digits 0 through 9, a sign. It can have a value not exceeding 18 decimal digits.

The formula for memory calculation of the COMP-3 with n digits (variable length + 1 byte for SIGN if exists) in the declaration is -

  • No. of bytes = Round ((n + 1)/2) - Where n is an odd number.
  • No. of bytes = Round (n/2) - Where n is an even number.
For example -

01 WS-VAR.
   05 WS-WIDTH     PIC S9(02) USAGE IS COMP-3.
   05 WS-AREA      PIC S9(06) COMP-3.

WS-AREA variable is declared as COMP-3, with a signed byte plus 6 digits. A total of 7 bytes and the (n+1)/2 formula will apply as n is an odd number. So, a total of 8/2 = 4 bytes allocated for WS-AREA.

COMP-4 | COMPUTATION-4 | COMP-5 | COMPUTATION-5 -

COMPUTATION-4 or COMP-4 or COMPUTATION-5 or COMP-5 is the equivalent of COMP or BINARY. The data items are represented in storage as binary data.