MainframeMaster

COBOL Tutorial

COBOL Divisions

Progress0 of 0 lessons

The Four COBOL Divisions Overview

COBOL programs are structured into four main divisions that organize code by function. This standardized structure is one of COBOL's defining characteristics, making programs more readable and maintainable. Each division has a specific purpose and must appear in a fixed sequence.

IDENTIFICATION DIVISION

Identifies the program with a name and optional metadata like author, date written, etc.

ENVIRONMENT DIVISION

Describes the computing environment, including file definitions and configuration.

DATA DIVISION

Defines all data items used by the program, including files, working storage, and parameters.

PROCEDURE DIVISION

Contains the actual executable instructions and business logic of the program.

This division-based structure reflects COBOL's business focus, separating program identification, environment configuration, data definition, and processing logic into distinct sections.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE-PROGRAM. ENVIRONMENT DIVISION. CONFIGURATION SECTION. INPUT-OUTPUT SECTION. DATA DIVISION. FILE SECTION. WORKING-STORAGE SECTION. PROCEDURE DIVISION. DISPLAY "Hello, World!". STOP RUN.

The example above shows the basic structure of a COBOL program with all four divisions.

IDENTIFICATION DIVISION Details and Purpose

The IDENTIFICATION DIVISION is the first division in a COBOL program and provides information about the program itself. This division is mandatory for every COBOL program.

Required Elements

  • The division header: IDENTIFICATION DIVISION.
  • The program name paragraph: PROGRAM-ID. program-name.

Optional Elements

  • AUTHOR. - Name of the programmer who wrote the program
  • INSTALLATION. - Name of the company or site where the program is used
  • DATE-WRITTEN. - Date when the program was written
  • DATE-COMPILED. - Date when the program was compiled
  • SECURITY. - Security classification of the program
  • REMARKS. - General comments about the program
cobol
1
2
3
4
5
6
IDENTIFICATION DIVISION. PROGRAM-ID. PAYROLL. AUTHOR. JOHN SMITH. DATE-WRITTEN. 2023-01-15. SECURITY. CONFIDENTIAL. REMARKS. THIS PROGRAM CALCULATES EMPLOYEE PAYROLL.

This example shows an IDENTIFICATION DIVISION with several optional elements included.

ENVIRONMENT DIVISION Details and Purpose

The ENVIRONMENT DIVISION describes the computing environment in which the program will run. It specifies the relationship between the program and external resources such as files and devices.

CONFIGURATION SECTION

Describes the overall configuration of the program, including:

  • SOURCE-COMPUTER - Specifies the computer used for compilation
  • OBJECT-COMPUTER - Specifies the computer where the program will run
  • SPECIAL-NAMES - Defines symbolic names for system devices or implements currency signs

INPUT-OUTPUT SECTION

Describes the files and external devices used by the program:

  • FILE-CONTROL - Assigns physical files to the program's internal file names
  • I-O-CONTROL - Specifies input-output techniques, such as file sharing or memory allocation
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-Z. OBJECT-COMPUTER. IBM-Z. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO EMPFILE ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS EMP-ID FILE STATUS IS FILE-STATUS-CODE. SELECT REPORT-FILE ASSIGN TO PRINTER.

This example shows an ENVIRONMENT DIVISION with file definitions for an indexed employee file and a report file.

DATA DIVISION Details and Purpose

The DATA DIVISION defines all the data items that will be used by the program, including file structures, variables, constants, and parameter interfaces. It's where you define the format and structure of your program's data.

FILE SECTION

Describes the structure of data files referenced in the ENVIRONMENT DIVISION, including record layouts and field definitions.

WORKING-STORAGE SECTION

Defines program variables that aren't associated with files, including temporary storage and constants.

LOCAL-STORAGE SECTION

Similar to WORKING-STORAGE but allocated each time a program is called and deallocated when it returns (for recursion support).

LINKAGE SECTION

Describes data items passed to the program from a calling program (parameters).

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5). 05 EMP-NAME PIC X(30). 05 EMP-SALARY PIC 9(7)V99. WORKING-STORAGE SECTION. 01 WS-VARIABLES. 05 WS-TOTAL-SALARY PIC 9(9)V99 VALUE ZERO. 05 WS-COUNTER PIC 9(3) VALUE ZERO. 05 WS-EOF PIC X VALUE 'N'. 05 FILE-STATUS-CODE PIC X(2).

This example shows a DATA DIVISION with file and working storage sections.

PROCEDURE DIVISION Details and Purpose

The PROCEDURE DIVISION contains the executable instructions of the program. This is where the actual processing logic is defined, including calculations, data manipulation, file operations, and decision-making.

Structure Components

  • Sections - Named groups of paragraphs (optional in modern COBOL)
  • Paragraphs - Named groups of sentences that can be referenced by PERFORM statements
  • Sentences - One or more statements ending with a period
  • Statements - COBOL verbs and their associated operands that perform actions

PROCEDURE DIVISION Header

May include parameter specifications:

  • PROCEDURE DIVISION. - Basic form with no parameters
  • PROCEDURE DIVISION USING parameter1, parameter2... - For receiving parameters
  • PROCEDURE DIVISION USING ... RETURNING result - For functions that return values
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. MAIN-LOGIC. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL WS-EOF = 'Y' PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT EMPLOYEE-FILE OPEN OUTPUT REPORT-FILE PERFORM READ-EMPLOYEE-RECORD. PROCESS-RECORDS. ADD EMP-SALARY TO WS-TOTAL-SALARY ADD 1 TO WS-COUNTER WRITE REPORT-RECORD FROM EMPLOYEE-RECORD PERFORM READ-EMPLOYEE-RECORD. READ-EMPLOYEE-RECORD. READ EMPLOYEE-FILE AT END MOVE 'Y' TO WS-EOF END-READ. TERMINATION. DISPLAY "Total employees: " WS-COUNTER DISPLAY "Total salary: $" WS-TOTAL-SALARY CLOSE EMPLOYEE-FILE CLOSE REPORT-FILE.

This example shows a PROCEDURE DIVISION with sections, paragraphs, and executable statements organized in a modular way.

Division Requirements and Sequence

The COBOL divisions must appear in a specific order, though not all divisions are always required:

Required Divisions

  • IDENTIFICATION DIVISION - Always required (PROGRAM-ID paragraph is mandatory)
  • PROCEDURE DIVISION - Required for executable programs (not required for copybooks)

Optional Divisions

  • ENVIRONMENT DIVISION - Optional, but required if the program uses files
  • DATA DIVISION - Optional, but almost always used in practical programs

Sequence Rules

  • Divisions must appear in this exact sequence: IDENTIFICATION, ENVIRONMENT, DATA, PROCEDURE
  • Divisions cannot be repeated
  • Each division ends when the next division begins or at the end of the program
  • Each division may contain specific sections that must also appear in a prescribed order

The strict structure of COBOL programs with these divisions contributes to readability and maintainability, especially for large business applications where many programmers might work on the same code over time.

Exercise: Analyzing COBOL Program Structure

Examine the following COBOL program and answer the questions:

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
IDENTIFICATION DIVISION. PROGRAM-ID. INVENTORY. AUTHOR. JANE DOE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT STOCK-FILE ASSIGN TO STOCKDAT ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD STOCK-FILE. 01 STOCK-RECORD. 05 ITEM-ID PIC X(10). 05 ITEM-NAME PIC X(30). 05 QUANTITY PIC 9(5). 05 UNIT-PRICE PIC 9(5)V99. WORKING-STORAGE SECTION. 01 WS-VARIABLES. 05 WS-TOTAL-VALUE PIC 9(10)V99 VALUE ZERO. 05 WS-EOF PIC X VALUE 'N'. PROCEDURE DIVISION. MAIN-PARAGRAPH. OPEN INPUT STOCK-FILE PERFORM UNTIL WS-EOF = 'Y' READ STOCK-FILE AT END MOVE 'Y' TO WS-EOF NOT AT END PERFORM PROCESS-RECORD END-READ END-PERFORM DISPLAY "Total inventory value: $" WS-TOTAL-VALUE CLOSE STOCK-FILE STOP RUN. PROCESS-RECORD. COMPUTE WS-TOTAL-VALUE = WS-TOTAL-VALUE + (QUANTITY * UNIT-PRICE).
  1. Identify all four COBOL divisions in this program.
  2. What is defined in the FILE SECTION of this program?
  3. What variables are defined in WORKING-STORAGE and what are their purposes?
  4. In the PROCEDURE DIVISION, how is the program handling the end-of-file condition?
  5. What calculation is being performed in the PROCESS-RECORD paragraph?

Test Your Knowledge

1. Which of the following COBOL divisions are mandatory in every program?

  • IDENTIFICATION DIVISION and PROCEDURE DIVISION
  • ENVIRONMENT DIVISION and DATA DIVISION
  • IDENTIFICATION DIVISION, ENVIRONMENT DIVISION, DATA DIVISION, and PROCEDURE DIVISION
  • Only IDENTIFICATION DIVISION

2. What is the purpose of the ENVIRONMENT DIVISION?

  • To define all variables used in the program
  • To describe the computing environment and file definitions
  • To contain all executable statements
  • To identify the program name and author

3. Which section in the DATA DIVISION would you use to define variables that are passed as parameters from a calling program?

  • FILE SECTION
  • WORKING-STORAGE SECTION
  • LOCAL-STORAGE SECTION
  • LINKAGE SECTION

4. In what order must COBOL divisions appear in a program?

5. What is the only mandatory paragraph in the IDENTIFICATION DIVISION?

FAQ

Can I omit any of the COBOL divisions in my program?

Yes, only the IDENTIFICATION DIVISION is absolutely mandatory for all COBOL programs. The PROCEDURE DIVISION is required for executable programs but not for copybooks. The ENVIRONMENT and DATA divisions are technically optional but are almost always included in practical programs, especially when working with files or variables.

What happens if I change the order of the divisions?

Changing the order of the divisions will cause compilation errors. COBOL requires the divisions to appear in the exact sequence: IDENTIFICATION, ENVIRONMENT, DATA, PROCEDURE. This strict structure is part of COBOL's design philosophy for clarity and readability.

Do all COBOL compilers require the same divisions?

While there are different dialects of COBOL (IBM COBOL, Micro Focus COBOL, GnuCOBOL, etc.), the four main divisions and their sequence are standard across all ANSI-compliant COBOL compilers. Some modern COBOL implementations might offer extensions or relaxed rules, but the core division structure remains the same.

Can I have multiple PROCEDURE DIVISIONS for different functionalities?

No, a COBOL program can have only one PROCEDURE DIVISION. To organize different functionalities, you should use sections and paragraphs within the PROCEDURE DIVISION or split your code into multiple programs that call each other. Modern COBOL also supports modules and object-oriented structures for better code organization.