COBOL Tutorial

Progress0 of 0 lessons

COBOL Program Initialization

Program initialization in COBOL involves setting up data structures, opening files, and preparing the program environment before main processing begins. Proper initialization ensures that all variables have known values, files are ready for access, and the program starts in a predictable state. Understanding initialization techniques is essential for writing reliable, maintainable COBOL programs.

What is Program Initialization?

Program initialization is the process of preparing a COBOL program for execution by setting initial values for variables, opening files, initializing counters and flags, and performing any setup required before the main processing logic begins. Initialization can occur at two levels:

  • Data Division Initialization: Using VALUE clauses to set initial values when data items are defined
  • Procedure Division Initialization: Using initialization sections and INITIALIZE statements to set up program state at runtime

Both approaches serve different purposes and are often used together to ensure complete program setup.

Initialization Sections in PROCEDURE DIVISION

The PROCEDURE DIVISION can be organized into sections, with an initialization section typically being the first section executed. This section contains paragraphs that perform setup tasks such as opening files, initializing counters, and setting up program state.

Basic Initialization Section Structure

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
37
38
IDENTIFICATION DIVISION. PROGRAM-ID. INITIALIZATION-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 RECORD-COUNTER PIC 9(6) VALUE 0. 01 FILE-STATUS-CODE PIC XX. 01 INITIALIZATION-FLAG PIC X VALUE 'N'. 88 INITIALIZATION-COMPLETE VALUE 'Y'. FILE SECTION. FD INPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 INPUT-RECORD PIC X(80). PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-PROGRAM. DISPLAY 'Starting program initialization...' MOVE 0 TO RECORD-COUNTER SET INITIALIZATION-COMPLETE TO TRUE DISPLAY 'Initialization complete' GO TO MAIN-PROCESSING. MAIN-PROCESSING SECTION. PROCESS-FILE. OPEN INPUT INPUT-FILE PERFORM UNTIL FILE-STATUS-CODE = '10' READ INPUT-FILE AT END MOVE '10' TO FILE-STATUS-CODE NOT AT END ADD 1 TO RECORD-COUNTER END-READ END-PERFORM CLOSE INPUT-FILE DISPLAY 'Records processed: ' RECORD-COUNTER STOP RUN.

In this example, the INITIALIZATION SECTION contains the INITIALIZE-PROGRAM paragraph, which sets up counters and flags before the main processing begins. The section name is followed by a period, and paragraphs within the section contain the initialization logic.

Initialization Section with Multiple Paragraphs

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
PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-DATA. INITIALIZE RECORD-COUNTER INITIALIZE ACCUMULATOR-TOTAL MOVE SPACES TO OUTPUT-MESSAGE DISPLAY 'Data items initialized'. OPEN-FILES. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE IF FILE-STATUS NOT = '00' DISPLAY 'Error opening files: ' FILE-STATUS STOP RUN END-IF DISPLAY 'Files opened successfully'. SET-UP-ENVIRONMENT. ACCEPT CURRENT-DATE FROM DATE ACCEPT CURRENT-TIME FROM TIME MOVE 'PROGRAM STARTED' TO LOG-MESSAGE DISPLAY LOG-MESSAGE GO TO MAIN-PROCESSING. MAIN-PROCESSING SECTION. PROCESS-RECORDS. *> Main processing logic here STOP RUN.

This example shows an initialization section with multiple paragraphs, each handling a specific aspect of initialization:

  • INITIALIZE-DATA: Resets data items to their initial values
  • OPEN-FILES: Opens all required files and checks for errors
  • SET-UP-ENVIRONMENT: Sets up date, time, and logging information

Using the INITIALIZE Verb

The INITIALIZE statement is a powerful verb that resets data items to their default values during program execution. It's commonly used in initialization sections to ensure data starts in a known state.

Basic INITIALIZE Statement

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
WORKING-STORAGE SECTION. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-BALANCE PIC 9(9)V99. 05 CUSTOMER-STATUS PIC X. PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-DATA. INITIALIZE CUSTOMER-RECORD DISPLAY 'Customer record initialized' DISPLAY 'ID: ' CUSTOMER-ID DISPLAY 'Name: ' CUSTOMER-NAME DISPLAY 'Balance: ' CUSTOMER-BALANCE DISPLAY 'Status: ' CUSTOMER-STATUS.

By default, the INITIALIZE statement sets:

  • Numeric fields: To ZEROES (0)
  • Alphabetic and alphanumeric fields: To SPACES
  • Alphanumeric-edited fields: To SPACES
  • National fields: To SPACES

INITIALIZE with REPLACING Clause

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
WORKING-STORAGE SECTION. 01 TRANSACTION-DATA. 05 TRANSACTION-ID PIC 9(6). 05 TRANSACTION-TYPE PIC X. 05 TRANSACTION-AMOUNT PIC 9(9)V99. 05 TRANSACTION-DESCRIPTION PIC X(40). PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-DATA. INITIALIZE TRANSACTION-DATA REPLACING NUMERIC DATA BY 999999 ALPHABETIC DATA BY 'UNKNOWN' ALPHANUMERIC DATA BY 'NOT SET' DISPLAY 'Transaction ID: ' TRANSACTION-ID DISPLAY 'Type: ' TRANSACTION-TYPE DISPLAY 'Amount: ' TRANSACTION-AMOUNT DISPLAY 'Description: ' TRANSACTION-DESCRIPTION.

The REPLACING clause allows you to specify custom initial values for different data categories:

  • NUMERIC DATA BY value: Sets all numeric fields to the specified value
  • ALPHABETIC DATA BY value: Sets alphabetic fields to the specified value
  • ALPHANUMERIC DATA BY value: Sets alphanumeric fields to the specified value
  • NUMERIC-EDITED DATA BY value: Sets numeric-edited fields to the specified value

Initializing Specific Fields

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
WORKING-STORAGE SECTION. 01 EMPLOYEE-DATA. 05 EMPLOYEE-ID PIC 9(6). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-DEPARTMENT PIC X(20). 05 EMPLOYEE-SALARY PIC 9(7)V99. 05 EMPLOYEE-STATUS PIC X. PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-SPECIFIC-FIELDS. *> Initialize only specific fields, not the entire group MOVE 0 TO EMPLOYEE-ID MOVE SPACES TO EMPLOYEE-NAME MOVE 'ACTIVE' TO EMPLOYEE-STATUS *> Or use INITIALIZE on individual fields INITIALIZE EMPLOYEE-SALARY INITIALIZE EMPLOYEE-DEPARTMENT DISPLAY 'Employee data initialized with specific values'.

You can initialize individual fields or use MOVE statements for more precise control over initialization values.

VALUE Clauses in Data Definition

VALUE clauses set initial values when data items are defined in the DATA DIVISION. These values are set before the PROCEDURE DIVISION begins execution, making them ideal for constants and default values.

Basic VALUE Clause Usage

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
WORKING-STORAGE SECTION. 01 INITIALIZED-VARIABLES. 05 COUNTER PIC 9(4) VALUE 0. 05 FLAG PIC X VALUE 'N'. 05 DEFAULT-AMOUNT PIC 9(6)V99 VALUE 1000.50. 05 DEFAULT-NAME PIC X(20) VALUE 'DEFAULT USER'. 05 STATUS-CODE PIC X VALUE 'A'. 88 ACTIVE-STATUS VALUE 'A'. 88 INACTIVE-STATUS VALUE 'I'. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY 'Counter: ' COUNTER DISPLAY 'Flag: ' FLAG DISPLAY 'Amount: ' DEFAULT-AMOUNT DISPLAY 'Name: ' DEFAULT-NAME IF ACTIVE-STATUS DISPLAY 'Status is active' END-IF.

VALUE clauses are evaluated at compile time and set initial values before program execution begins. They're particularly useful for:

  • Counters and accumulators: Starting at zero or a specific value
  • Flags and status indicators: Setting default states
  • Constants: Values that don't change during execution
  • Default values: Initial values that may be changed later

VALUE with Figurative Constants

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
WORKING-STORAGE SECTION. 01 DEFAULT-DATA. 05 NUMERIC-FIELD PIC 9(6) VALUE ZERO. 05 ALPHANUMERIC-FIELD PIC X(30) VALUE SPACES. 05 BINARY-FIELD PIC X(4) VALUE LOW-VALUES. 05 HIGH-VALUE-FIELD PIC X(4) VALUE HIGH-VALUES. 05 QUOTE-FIELD PIC X(10) VALUE QUOTES. PROCEDURE DIVISION. DISPLAY-DEFAULTS. DISPLAY 'Numeric (ZERO): ' NUMERIC-FIELD DISPLAY 'Alphanumeric (SPACES): ' ALPHANUMERIC-FIELD DISPLAY 'Binary (LOW-VALUES): ' BINARY-FIELD DISPLAY 'High value: ' HIGH-VALUE-FIELD DISPLAY 'Quotes: ' QUOTE-FIELD.

COBOL provides figurative constants that can be used in VALUE clauses:

  • ZERO or ZEROES: Sets numeric fields to zero
  • SPACE or SPACES: Sets alphanumeric fields to spaces
  • LOW-VALUE or LOW-VALUES: Sets fields to the lowest possible value (binary zeros)
  • HIGH-VALUE or HIGH-VALUES: Sets fields to the highest possible value (binary ones)
  • QUOTE or QUOTES: Sets fields to quotation marks

Complete Initialization Example

Here's a comprehensive example showing a complete program initialization pattern:

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
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
IDENTIFICATION DIVISION. PROGRAM-ID. COMPLETE-INITIALIZATION. AUTHOR. MAINFRAME MASTER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO CUSTFILE ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE RECORD CONTAINS 100 CHARACTERS. 01 CUSTOMER-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 PROGRAM-COUNTERS. 05 RECORDS-READ PIC 9(6) VALUE 0. 05 RECORDS-PROCESSED PIC 9(6) VALUE 0. 05 RECORDS-ERROR PIC 9(6) VALUE 0. 01 FILE-STATUS-FIELDS. 05 CUSTOMER-FILE-STATUS PIC XX VALUE '00'. 01 PROGRAM-FLAGS. 05 INITIALIZATION-COMPLETE PIC X VALUE 'N'. 88 INIT-COMPLETE VALUE 'Y'. 05 END-OF-FILE PIC X VALUE 'N'. 88 EOF VALUE 'Y'. 01 DATE-TIME-INFO. 05 CURRENT-DATE PIC 9(8). 05 CURRENT-TIME PIC 9(6). 01 ERROR-MESSAGE PIC X(80) VALUE SPACES. PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-PROGRAM. DISPLAY '========================================' DISPLAY 'PROGRAM INITIALIZATION STARTING' DISPLAY '========================================' *> Initialize counters INITIALIZE PROGRAM-COUNTERS *> Initialize flags SET INIT-COMPLETE TO TRUE SET EOF TO FALSE *> Get current date and time ACCEPT CURRENT-DATE FROM DATE ACCEPT CURRENT-TIME FROM TIME DISPLAY 'Program started: ' CURRENT-DATE ' at ' CURRENT-TIME *> Open files OPEN INPUT CUSTOMER-FILE IF CUSTOMER-FILE-STATUS NOT = '00' MOVE 'ERROR: Failed to open customer file' TO ERROR-MESSAGE DISPLAY ERROR-MESSAGE DISPLAY 'File status: ' CUSTOMER-FILE-STATUS STOP RUN END-IF DISPLAY 'Customer file opened successfully' DISPLAY '========================================' DISPLAY 'INITIALIZATION COMPLETE' DISPLAY '========================================' GO TO MAIN-PROCESSING. MAIN-PROCESSING SECTION. PROCESS-FILE. PERFORM UNTIL EOF READ CUSTOMER-FILE AT END SET EOF TO TRUE NOT AT END ADD 1 TO RECORDS-READ *> Process record here ADD 1 TO RECORDS-PROCESSED END-READ END-PERFORM CLOSE CUSTOMER-FILE DISPLAY '========================================' DISPLAY 'PROCESSING SUMMARY' DISPLAY '========================================' DISPLAY 'Records read: ' RECORDS-READ DISPLAY 'Records processed: ' RECORDS-PROCESSED DISPLAY 'Records with errors: ' RECORDS-ERROR DISPLAY '========================================' STOP RUN.

This example demonstrates a complete initialization pattern that includes:

  • Counter initialization: Using INITIALIZE to reset all counters
  • Flag setup: Setting condition names to known states
  • Date/time capture: Getting system date and time
  • File operations: Opening files with error checking
  • Error handling: Checking file status and handling errors
  • User feedback: Displaying initialization progress

Initialization Best Practices

Following best practices ensures reliable and maintainable program initialization:

1. Use VALUE Clauses for Default Values

Prefer VALUE clauses in the DATA DIVISION for setting initial values that should be established before program execution begins. This is more efficient than runtime initialization for constants and defaults.

cobol
1
2
3
4
5
6
7
8
9
WORKING-STORAGE SECTION. *> Good: Use VALUE clause for initial values 01 COUNTER PIC 9(6) VALUE 0. 01 DEFAULT-FLAG PIC X VALUE 'N'. *> Avoid: Initializing in PROCEDURE DIVISION when VALUE would work PROCEDURE DIVISION. MOVE 0 TO COUNTER *> Unnecessary if VALUE clause used MOVE 'N' TO DEFAULT-FLAG.

2. Use INITIALIZE for Runtime Reset

Use the INITIALIZE statement when you need to reset data items during program execution, such as when processing multiple transactions or reusing data structures.

cobol
1
2
3
4
5
6
7
8
9
PROCEDURE DIVISION. PROCESS-TRANSACTIONS. PERFORM UNTIL NO-MORE-TRANSACTIONS *> Reset transaction data for each new transaction INITIALIZE TRANSACTION-RECORD *> Process transaction READ TRANSACTION-FILE *> ... process transaction ... END-PERFORM.

3. Organize Initialization in Sections

Use initialization sections to clearly separate setup code from main processing logic, improving readability and maintainability.

4. Check File Status After Opening Files

Always check file status codes after opening files to catch errors early and provide meaningful error messages.

cobol
1
2
3
4
5
6
7
8
INITIALIZATION SECTION. OPEN-FILES. OPEN INPUT INPUT-FILE IF FILE-STATUS NOT = '00' DISPLAY 'ERROR: Cannot open input file' DISPLAY 'File status: ' FILE-STATUS STOP RUN END-IF.

5. Initialize All Counters and Accumulators

Ensure all counters, accumulators, and flags are initialized to known values before use to prevent unpredictable behavior.

6. Avoid Initializing Large Tables Unnecessarily

Be cautious when initializing large tables or data structures, as this can impact performance. Only initialize what's necessary.

Common Initialization Patterns

Pattern 1: Simple Counter Initialization

cobol
1
2
3
4
5
6
7
8
9
10
WORKING-STORAGE SECTION. 01 COUNTERS. 05 RECORD-COUNT PIC 9(6) VALUE 0. 05 ERROR-COUNT PIC 9(6) VALUE 0. PROCEDURE DIVISION. INITIALIZATION SECTION. RESET-COUNTERS. MOVE 0 TO RECORD-COUNT MOVE 0 TO ERROR-COUNT.

Pattern 2: File and Data Initialization

cobol
1
2
3
4
5
6
7
8
9
10
11
12
PROCEDURE DIVISION. INITIALIZATION SECTION. SETUP-PROGRAM. *> Initialize data INITIALIZE WORKING-DATA *> Open files OPEN INPUT INPUT-FILE OUTPUT OUTPUT-FILE *> Check for errors IF FILE-STATUS NOT = '00' PERFORM ERROR-HANDLER END-IF.

Pattern 3: Conditional Initialization

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-BASED-ON-MODE. EVALUATE PROCESSING-MODE WHEN 'FULL' INITIALIZE ALL-DATA-STRUCTURES OPEN ALL-FILES WHEN 'PARTIAL' INITIALIZE SELECTED-DATA OPEN INPUT-FILE ONLY WHEN 'TEST' INITIALIZE TEST-DATA OPEN TEST-FILE END-EVALUATE.

Initialization Error Handling

Proper error handling during initialization prevents programs from continuing with invalid states:

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
PROCEDURE DIVISION. INITIALIZATION SECTION. INITIALIZE-WITH-ERROR-CHECKING. *> Initialize data INITIALIZE PROGRAM-DATA *> Open files with error checking OPEN INPUT REQUIRED-FILE IF FILE-STATUS NOT = '00' MOVE 'CRITICAL ERROR: Cannot open required file' TO ERROR-MESSAGE DISPLAY ERROR-MESSAGE DISPLAY 'File status code: ' FILE-STATUS PERFORM CLEANUP-AND-EXIT STOP RUN END-IF *> Validate initialization IF NOT INITIALIZATION-VALID DISPLAY 'ERROR: Initialization validation failed' PERFORM CLEANUP-AND-EXIT STOP RUN END-IF DISPLAY 'Initialization completed successfully' GO TO MAIN-PROCESSING. CLEANUP-AND-EXIT. *> Close any opened files IF FILE-STATUS = '00' CLOSE REQUIRED-FILE END-IF DISPLAY 'Program terminated due to initialization error'.

Summary

Program initialization is a critical aspect of COBOL programming that ensures programs start in a predictable state. Key points to remember:

  • Use initialization sections to organize setup code separately from main processing
  • VALUE clauses set initial values at compile time, ideal for constants and defaults
  • INITIALIZE statements reset data at runtime, useful for reusing data structures
  • Always check file status after opening files to catch errors early
  • Initialize all counters and flags to known values before use
  • Handle initialization errors gracefully with proper cleanup
  • Use figurative constants like ZERO, SPACES, and LOW-VALUES for clarity

Proper initialization practices lead to more reliable, maintainable, and debuggable COBOL programs.

Test Your Knowledge

1. What is the primary purpose of an initialization section in the PROCEDURE DIVISION?

  • To define data structures
  • To set up program state, open files, and prepare for main processing
  • To perform the main business logic
  • To handle errors

2. What is the difference between VALUE clauses and INITIALIZE statements?

  • There is no difference
  • VALUE clauses set initial values at compile time in the DATA DIVISION, while INITIALIZE statements reset data at runtime in the PROCEDURE DIVISION
  • VALUE clauses are only for numeric fields
  • INITIALIZE statements can only be used in initialization sections

3. What default values does the INITIALIZE statement set for different data types?

  • All fields to ZERO
  • Numeric fields to ZEROES, alphabetic/alphanumeric fields to SPACES
  • All fields to SPACES
  • All fields to LOW-VALUES

4. When should you use VALUE clauses versus INITIALIZE statements?

  • Always use INITIALIZE statements
  • Use VALUE clauses for initial values set at compile time, and INITIALIZE for runtime resets
  • Always use VALUE clauses
  • They are interchangeable

5. What should you always do after opening files in an initialization section?

  • Nothing, files always open successfully
  • Check the file status code to ensure the file opened correctly
  • Immediately start reading from the file
  • Close the file immediately

Related Pages