COBOL Tutorial

Progress0 of 0 lessons

COBOL Variable Control

Variable control in COBOL involves managing variable scope (where variables can be accessed), lifetime (when variables exist in memory), and initialization (how variables get their initial values). Understanding variable control is essential for writing correct, efficient, and maintainable COBOL programs, especially when dealing with reentrant programs, parameter passing, and memory management.

Understanding Variable Control

Variable control encompasses three key aspects:

  • Scope: Where in the program a variable can be accessed
  • Lifetime: When a variable exists in memory (allocation and deallocation)
  • Initialization: How and when a variable gets its initial value

Storage Sections and Variable Control

COBOL provides three main storage sections, each with different characteristics for variable control:

Variable control characteristics by storage section
Storage SectionScopeLifetimeInitialization
WORKING-STORAGEEntire programProgram duration (persists across calls)Once at program start (or each entry if INITIAL)
LOCAL-STORAGEEntire programProgram invocation (reinitialized on each call)Each time program is invoked
LINKAGEEntire programManaged by calling programSet by calling program

WORKING-STORAGE SECTION

WORKING-STORAGE variables are allocated when the program starts and persist for the entire program execution. They maintain their values between procedure calls unless the program has the INITIAL attribute.

Characteristics

  • Allocation: When program starts
  • Lifetime: Entire program execution
  • Persistence: Values persist across procedure calls
  • Initialization: Once at program start (VALUE clauses)
  • Use Case: Program-level state, counters, accumulators, configuration

WORKING-STORAGE Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
DATA DIVISION. WORKING-STORAGE SECTION. *> Program-level variables that persist 01 WS-PROGRAM-CONTROL. 05 WS-PROGRAM-NAME PIC X(8) VALUE 'MAINPROG'. 05 WS-EXECUTION-COUNT PIC 9(6) VALUE ZERO. 05 WS-START-TIME PIC X(8). *> Constants initialized once 01 WS-CONSTANTS. 05 WS-MAX-RECORDS PIC 9(6) VALUE 100000. 05 WS-TIMEOUT-VALUE PIC 9(4) VALUE 3000. 05 WS-SUCCESS-CODE PIC X(2) VALUE '00'. *> Work areas that persist across calls 01 WS-WORK-AREAS. 05 WS-ACCUMULATOR PIC S9(15)V99 COMP-3 VALUE ZERO. 05 WS-RECORD-COUNT PIC 9(8) VALUE ZERO. 05 WS-ERROR-COUNT PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. *> These variables maintain values across procedure calls ADD 1 TO WS-EXECUTION-COUNT PERFORM PROCESS-DATA *> WS-EXECUTION-COUNT still has the incremented value PERFORM PROCESS-DATA *> WS-EXECUTION-COUNT continues to accumulate PROCESS-DATA. *> Can access all WORKING-STORAGE variables ADD 1 TO WS-RECORD-COUNT *> WS-RECORD-COUNT persists between calls to this procedure.

INITIAL Attribute

Programs with the INITIAL attribute reinitialize WORKING-STORAGE on each program entry:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
IDENTIFICATION DIVISION. PROGRAM-ID. REENTRANT-PROG INITIAL. *> INITIAL attribute causes WORKING-STORAGE to be *> reinitialized each time the program is called DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-COUNTER PIC 9(6) VALUE ZERO. *> This will be reset to ZERO on each program entry PROCEDURE DIVISION. *> Each time this program is called, WS-COUNTER starts at ZERO ADD 1 TO WS-COUNTER *> Process data EXEC CICS RETURN END-EXEC.

LOCAL-STORAGE SECTION

LOCAL-STORAGE variables are allocated each time the program is invoked and deallocated when the program exits. This provides fresh values on each program call, making it ideal for reentrant programs.

Characteristics

  • Allocation: Each time program is invoked
  • Lifetime: Program invocation duration
  • Persistence: Values do NOT persist between invocations
  • Initialization: Each time program is invoked (VALUE clauses)
  • Use Case: Reentrant programs, temporary work areas, fresh data on each call

LOCAL-STORAGE Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
DATA DIVISION. LOCAL-STORAGE SECTION. *> Variables reinitialized on each program call 01 LS-TEMPORARY-WORK. 05 LS-TEMP-BUFFER PIC X(1000). 05 LS-CALCULATION-AREA PIC S9(15)V99 COMP-3. 05 LS-INDEX PIC 9(4) VALUE ZERO. *> Reentrant program data 01 LS-PROCESSING-DATA. 05 LS-INPUT-RECORD PIC X(200). 05 LS-OUTPUT-RECORD PIC X(200). 05 LS-PROCESSING-FLAG PIC X VALUE 'N'. 88 LS-PROCESSING VALUE 'Y'. 88 LS-NOT-PROCESSING VALUE 'N'. PROCEDURE DIVISION. MAIN-PROCESS. *> Each time program is called, LS-INDEX starts at ZERO *> LS-PROCESSING-FLAG starts at 'N' *> All LOCAL-STORAGE variables are fresh PERFORM PROCESS-DATA *> When program exits, LOCAL-STORAGE is deallocated *> Next invocation gets fresh values again PROCESS-DATA. *> Can access all LOCAL-STORAGE variables ADD 1 TO LS-INDEX *> LS-INDEX is fresh on each program invocation.

LINKAGE SECTION

LINKAGE SECTION defines variables that reference storage allocated by the calling program. These variables don't have storage allocated within the program itself.

Characteristics

  • Allocation: By calling program
  • Lifetime: Managed by calling program
  • Persistence: Depends on calling program
  • Initialization: Set by calling program
  • Use Case: Parameters, system interfaces, shared data

LINKAGE SECTION Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
DATA DIVISION. LINKAGE SECTION. *> Parameters passed from calling program 01 PARAMETER-LIST. 05 PARM-LENGTH PIC S9(4) COMP. 05 PARM-DATA PIC X(100). *> Return area shared with caller 01 RETURN-AREA. 05 RETURN-CODE PIC 9(4) COMP. 05 RETURN-MESSAGE PIC X(50). *> Shared data area 01 SHARED-DATA. 05 SHARED-VARIABLE PIC 9(6). 05 SHARED-FLAG PIC X. PROCEDURE DIVISION USING PARAMETER-LIST RETURN-AREA SHARED-DATA. *> These variables reference storage allocated by caller *> Changes to these variables affect the calling program *> No storage is allocated within this program *> Access parameters IF PARM-LENGTH > 0 PERFORM PROCESS-PARAMETERS END-IF *> Set return values MOVE 0 TO RETURN-CODE MOVE 'SUCCESS' TO RETURN-MESSAGE *> Modify shared data ADD 1 TO SHARED-VARIABLE *> This change is visible to the calling program.

Variable Initialization

Understanding when and how variables are initialized is crucial for variable control.

Initialization Methods

Variable initialization methods
MethodWhenApplies To
VALUE clauseAt allocation timeWORKING-STORAGE, LOCAL-STORAGE
INITIALIZE statementExplicitly in program codeAny storage section
MOVE statementExplicitly in program codeAny storage section
Calling programBefore program callLINKAGE SECTION

Initialization Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
DATA DIVISION. WORKING-STORAGE SECTION. *> Initialized with VALUE clause at program start 01 WS-COUNTER PIC 9(6) VALUE ZERO. 01 WS-FLAG PIC X VALUE 'N'. 01 WS-NAME PIC X(30) VALUE SPACES. *> Not initialized - may have undefined values 01 WS-UNINITIALIZED PIC 9(6). 01 WS-BUFFER PIC X(100). PROCEDURE DIVISION. MAIN-PROCESS. *> Explicit initialization using INITIALIZE INITIALIZE WS-UNINITIALIZED INITIALIZE WS-BUFFER *> Explicit initialization using MOVE MOVE ZERO TO WS-COUNTER MOVE 'Y' TO WS-FLAG MOVE SPACES TO WS-NAME *> Initialize group item INITIALIZE WS-DATA-GROUP REPLACING NUMERIC DATA BY ZERO ALPHABETIC DATA BY SPACES.

AUTOMATIC Clause

The AUTOMATIC clause provides automatic storage management, allocating storage when first accessed and deallocating when out of scope.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
DATA DIVISION. WORKING-STORAGE SECTION. *> Automatic storage - allocated when first accessed 01 WS-AUTOMATIC-VAR PIC 9(6) AUTOMATIC VALUE ZERO. LOCAL-STORAGE SECTION. *> Automatic storage in LOCAL-STORAGE 01 LS-AUTOMATIC-BUFFER PIC X(200) AUTOMATIC. PROCEDURE DIVISION. MAIN-PROCESS. *> Storage allocated when first accessed ADD 1 TO WS-AUTOMATIC-VAR *> Storage automatically managed *> Deallocated when program exits (for LOCAL-STORAGE) *> Or when out of scope (for AUTOMATIC items).

Choosing the Right Storage Section

Choosing the appropriate storage section
RequirementUse This SectionReason
Variables that persist across procedure callsWORKING-STORAGEMaintains values throughout program execution
Reentrant program (fresh values on each call)LOCAL-STORAGEReinitialized on each program invocation
Parameters passed from calling programLINKAGE SECTIONReferences external storage from caller
Temporary work areasLOCAL-STORAGEFresh values, automatically cleaned up
Program-level counters and accumulatorsWORKING-STORAGEPersist and accumulate across calls
Shared data between programsLINKAGE SECTIONReferences storage managed by caller

Variable Scope in COBOL

In COBOL, variables declared in WORKING-STORAGE, LOCAL-STORAGE, or LINKAGE sections are accessible throughout the entire program. COBOL doesn't have block-level scope like some languages.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-GLOBAL-VAR PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. *> WS-GLOBAL-VAR is accessible here ADD 1 TO WS-GLOBAL-VAR PERFORM SUB-PROCESS-1 PERFORM SUB-PROCESS-2 *> WS-GLOBAL-VAR is still accessible and retains its value SUB-PROCESS-1. *> WS-GLOBAL-VAR is accessible here too ADD 10 TO WS-GLOBAL-VAR *> Changes are visible to all procedures SUB-PROCESS-2. *> WS-GLOBAL-VAR is accessible here as well *> Can see changes made in SUB-PROCESS-1 DISPLAY 'Value: ' WS-GLOBAL-VAR.

Best Practices

1. Use Appropriate Storage Sections

Choose the storage section that matches your variable's lifetime and initialization requirements. Use WORKING-STORAGE for persistent state, LOCAL-STORAGE for reentrant programs, and LINKAGE for parameters.

2. Initialize Variables Explicitly

Always initialize variables explicitly using VALUE clauses or INITIALIZE statements. Don't rely on undefined initial values.

3. Use LOCAL-STORAGE for Reentrant Programs

If your program needs to be reentrant (can be called by multiple tasks simultaneously), use LOCAL-STORAGE to ensure each invocation gets fresh values.

4. Document Variable Lifetime

Add comments explaining why you chose a particular storage section, especially for complex programs where variable lifetime is critical.

5. Be Careful with WORKING-STORAGE in Reentrant Programs

Avoid using WORKING-STORAGE for task-specific data in reentrant programs, as it can cause data corruption when multiple tasks execute the program simultaneously.

Common Patterns

Pattern 1: Program-Level State

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
*> Use WORKING-STORAGE for program-level state WORKING-STORAGE SECTION. 01 WS-PROGRAM-STATE. 05 WS-RECORD-COUNT PIC 9(8) VALUE ZERO. 05 WS-TOTAL-AMOUNT PIC S9(15)V99 COMP-3 VALUE ZERO. 05 WS-ERROR-COUNT PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. *> These variables accumulate across all procedure calls PERFORM PROCESS-RECORDS *> WS-RECORD-COUNT, WS-TOTAL-AMOUNT persist PERFORM GENERATE-REPORT *> Can use accumulated values.

Pattern 2: Reentrant Program

cobol
1
2
3
4
5
6
7
8
9
10
11
*> Use LOCAL-STORAGE for reentrant programs LOCAL-STORAGE SECTION. 01 LS-PROCESSING-DATA. 05 LS-INPUT-BUFFER PIC X(200). 05 LS-OUTPUT-BUFFER PIC X(200). 05 LS-TEMP-VALUES PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. *> Each program invocation gets fresh values *> Multiple tasks can call this program simultaneously *> Each gets its own copy of LOCAL-STORAGE variables.

Pattern 3: Parameter Passing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
*> Use LINKAGE SECTION for parameters LINKAGE SECTION. 01 INPUT-PARAMETERS. 05 PARM-LENGTH PIC S9(4) COMP. 05 PARM-DATA PIC X(100). 01 OUTPUT-RESULTS. 05 RESULT-CODE PIC 9(4) COMP. 05 RESULT-MESSAGE PIC X(50). PROCEDURE DIVISION USING INPUT-PARAMETERS OUTPUT-RESULTS. *> Parameters reference storage from calling program *> Changes to OUTPUT-RESULTS are visible to caller.

Explain It Like I'm 5 Years Old

Imagine you have different types of boxes for your toys:

WORKING-STORAGE is like a big box in your room that stays there all the time. You put toys in it, and they stay there even when you're not playing. The next time you play, your toys are still in the box where you left them.

LOCAL-STORAGE is like a temporary box you get each time you start playing. When you're done playing, the box goes away. The next time you play, you get a brand new empty box to start fresh.

LINKAGE is like sharing a box with your friend. You both use the same box, and if you put something in it, your friend can see it too. The box belongs to your friend, but you can use it together.

Just like you choose different boxes for different toys, COBOL programs choose different storage sections for different types of data!

Exercises

Exercise 1: Choose Storage Section

For each scenario, choose the appropriate storage section:

  • A counter that accumulates across multiple procedure calls
  • Input parameters passed from another program
  • Temporary work area in a reentrant program
cobol
1
2
3
4
5
6
7
8
9
10
11
*> 1. Counter - use WORKING-STORAGE (persists) WORKING-STORAGE SECTION. 01 WS-ACCUMULATOR PIC 9(8) VALUE ZERO. *> 2. Parameters - use LINKAGE SECTION LINKAGE SECTION. 01 INPUT-PARMS PIC X(100). *> 3. Temporary work - use LOCAL-STORAGE (fresh each call) LOCAL-STORAGE SECTION. 01 LS-TEMP-AREA PIC X(200).

Exercise 2: Initialize Variables

Write code to properly initialize a group of variables including numeric, alphabetic, and mixed data types.

cobol
1
2
3
4
5
6
7
8
9
10
11
WORKING-STORAGE SECTION. 01 WS-DATA-GROUP. 05 WS-NUMERIC-FIELD PIC 9(6). 05 WS-ALPHABETIC-FIELD PIC X(30). 05 WS-MIXED-FIELD PIC X(10). PROCEDURE DIVISION. *> Initialize all fields INITIALIZE WS-DATA-GROUP REPLACING NUMERIC DATA BY ZERO ALPHABETIC DATA BY SPACES.

Test Your Knowledge

1. When are WORKING-STORAGE variables initialized?

  • Every time a procedure is called
  • Once when the program starts
  • Only when explicitly initialized
  • Never - they start with random values

2. What is the main difference between WORKING-STORAGE and LOCAL-STORAGE?

  • There is no difference
  • WORKING-STORAGE persists across program calls, LOCAL-STORAGE is reinitialized on each invocation
  • LOCAL-STORAGE is faster
  • WORKING-STORAGE can only hold numeric data

3. What does the LINKAGE SECTION contain?

  • Program constants
  • Variables that reference storage allocated by the calling program
  • Temporary work areas
  • File record definitions

4. When should you use LOCAL-STORAGE instead of WORKING-STORAGE?

  • Never - always use WORKING-STORAGE
  • When you need variables reinitialized on each program invocation, such as in reentrant programs
  • Only for numeric variables
  • Only for file operations

5. What does the AUTOMATIC clause do?

  • Makes variables initialize automatically
  • Allocates storage when first accessed and deallocates when out of scope
  • Makes variables accessible everywhere
  • Speeds up variable access

Related Pages