MainframeMaster

COBOL Tutorial

COBOL Program Structure

Progress0 of 0 lessons

Introduction to COBOL Program Structure

Every COBOL program follows a standardized structure consisting of four main divisions. This structured approach ensures consistency, readability, and maintainability across all COBOL applications. Understanding this structure is fundamental to COBOL programming.

The Four Divisions

COBOL programs are organized into four distinct divisions, each serving a specific purpose:

  1. IDENTIFICATION DIVISION - Program identification and documentation
  2. ENVIRONMENT DIVISION - Hardware and software environment specifications
  3. DATA DIVISION - Data definitions and file descriptions
  4. PROCEDURE DIVISION - Program logic and executable statements

These divisions must appear in this exact order, and each division has specific rules about what can be included within it.

Basic Program Structure

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
IDENTIFICATION DIVISION. PROGRAM-ID. program-name. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. computer-name. OBJECT-COMPUTER. computer-name. DATA DIVISION. WORKING-STORAGE SECTION. 01 variable-name PIC X(10). PROCEDURE DIVISION. MAIN-PROCESS. DISPLAY "Hello, World!" STOP RUN.

This is the minimal structure for a COBOL program. Each division can be expanded with additional entries depending on the program's requirements.

Division Hierarchy

DivisionRequiredPurposeContent
IDENTIFICATIONYesProgram identificationPROGRAM-ID, documentation
ENVIRONMENTYesSystem configurationHardware, software, files
DATAYesData definitionsVariables, files, records
PROCEDUREYesProgram logicExecutable statements

IDENTIFICATION DIVISION

The IDENTIFICATION DIVISION serves as the program header and contains documentation about the program. It is the first division in every COBOL program and provides essential information for program identification and management.

Required and Optional Paragraphs

The IDENTIFICATION DIVISION contains one required paragraph and several optional ones:

cobol
1
2
3
4
5
6
7
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESSING. AUTHOR. JOHN DOE. DATE-WRITTEN. 12/31/2023. DATE-COMPILED. 01/15/2024. SECURITY. CONFIDENTIAL. REMARKS. This program processes customer data.

Only PROGRAM-ID is required. All other paragraphs are optional and serve documentation purposes.

PROGRAM-ID Paragraph

The PROGRAM-ID paragraph is mandatory and specifies the program name:

cobol
1
2
3
4
5
6
7
8
* Basic PROGRAM-ID PROGRAM-ID. SALES-REPORT. * PROGRAM-ID with comment PROGRAM-ID. CUSTOMER-MAINTENANCE. * PROGRAM-ID with common name (optional) PROGRAM-ID. INVENTORY-SYSTEM IS COMMON.

The program name must be unique within the system and follows COBOL naming conventions. The IS COMMON clause is optional and indicates the program can be called by other programs.

Documentation Paragraphs

Optional paragraphs provide additional documentation:

ParagraphPurposeExample
AUTHORProgram authorAUTHOR. JOHN DOE.
DATE-WRITTENCreation dateDATE-WRITTEN. 12/31/2023.
DATE-COMPILEDCompilation dateDATE-COMPILED. 01/15/2024.
SECURITYSecurity levelSECURITY. CONFIDENTIAL.
REMARKSAdditional notesREMARKS. Customer data processing.

ENVIRONMENT DIVISION

The ENVIRONMENT DIVISION describes the computing environment in which the program will run. It specifies hardware and software dependencies, file configurations, and system-specific information. This division is required but can be minimal in modern COBOL implementations.

Division Structure

The ENVIRONMENT DIVISION consists of two main sections:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-3090. OBJECT-COMPUTER. IBM-3090. SPECIAL-NAMES. CURRENCY SIGN IS "$". INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT". I-O-CONTROL. SAME RECORD AREA FOR CUSTOMER-FILE, BACKUP-FILE.

The CONFIGURATION SECTION describes the computing environment, while the INPUT-OUTPUT SECTION handles file configurations and I/O control.

CONFIGURATION SECTION

This section contains three main paragraphs:

ParagraphPurposeExample
SOURCE-COMPUTERDevelopment environmentSOURCE-COMPUTER. IBM-3090.
OBJECT-COMPUTERExecution environmentOBJECT-COMPUTER. IBM-3090.
SPECIAL-NAMESSystem-specific namesCURRENCY SIGN IS "$".

INPUT-OUTPUT SECTION

This section handles file and I/O configurations:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-STATUS. SELECT REPORT-FILE ASSIGN TO "REPORT.TXT" ORGANIZATION IS LINE SEQUENTIAL. I-O-CONTROL. SAME RECORD AREA FOR CUSTOMER-FILE, BACKUP-FILE APPLY WRITE-ONLY ON CUSTOMER-FILE.

FILE-CONTROL defines file characteristics, while I-O-CONTROL specifies I/O behavior and optimizations.

Modern Usage

In contemporary COBOL environments, the ENVIRONMENT DIVISION is often simplified:

cobol
1
2
3
4
ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT".

Many modern COBOL compilers provide defaults for hardware specifications, making the CONFIGURATION SECTION optional in many cases.

DATA DIVISION

The DATA DIVISION defines all data structures used by the program. It describes variables, file records, constants, and data relationships. This division is required and contains the data definitions that the PROCEDURE DIVISION will manipulate.

Division Sections

The DATA DIVISION consists of three main sections:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(45). WORKING-STORAGE SECTION. 01 WS-COUNTER PIC 9(3) VALUE 0. 01 WS-TOTAL-AMOUNT PIC 9(7)V99 VALUE 0. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. LINKAGE SECTION. 01 LS-PARAMETER PIC X(10).

Each section serves a specific purpose in data management and program communication.

FILE SECTION

The FILE SECTION defines external file structures:

  • File Description (FD) - Defines file characteristics and record layouts
  • Record Descriptions - Define the structure of records within files
  • Report Section - Defines report layouts (when using Report Writer)

The FILE SECTION is required only when the program processes files. Each file used by the program must have a corresponding FD entry.

WORKING-STORAGE SECTION

The WORKING-STORAGE SECTION defines internal program variables:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
WORKING-STORAGE SECTION. * Simple variables 01 WS-COUNTER PIC 9(3) VALUE 0. 01 WS-TOTAL-AMOUNT PIC 9(7)V99 VALUE 0. 01 WS-CUSTOMER-NAME PIC X(30). * Constants 01 WS-CONSTANTS. 05 WS-MAX-RECORDS PIC 9(5) VALUE 10000. 05 WS-TAX-RATE PIC V999 VALUE .08. * Condition names 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 88 NOT-END-OF-FILE VALUE 'N'. * Group items 01 WS-DATE-FIELDS. 05 WS-YEAR PIC 9(4). 05 WS-MONTH PIC 9(2). 05 WS-DAY PIC 9(2).

WORKING-STORAGE variables exist only during program execution and are used for temporary data storage and calculations.

LINKAGE SECTION

The LINKAGE SECTION defines parameters passed between programs:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
LINKAGE SECTION. * Input parameters 01 LS-CUSTOMER-ID PIC X(5). 01 LS-ACTION-CODE PIC X. * Output parameters 01 LS-RETURN-CODE PIC 9(2). 01 LS-ERROR-MESSAGE PIC X(50). * Complex parameter structure 01 LS-PARAMETER-BLOCK. 05 LS-FUNCTION-CODE PIC X. 05 LS-DATA-LENGTH PIC 9(4). 05 LS-DATA-AREA PIC X(100).

The LINKAGE SECTION is used when programs communicate with each other or when the program receives parameters from the calling environment.

Section Requirements

SectionRequiredWhen Used
FILE SECTIONNoWhen processing files
WORKING-STORAGE SECTIONNoWhen using variables
LINKAGE SECTIONNoWhen receiving parameters

PROCEDURE DIVISION

The PROCEDURE DIVISION contains all the executable statements and program logic. It is the heart of the COBOL program where the actual processing occurs. This division is required and contains the instructions that tell the computer what to do.

Division Structure

The PROCEDURE DIVISION consists of paragraphs and sections:

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
PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE MOVE 0 TO WS-RECORD-COUNT. PROCESS-DATA. PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE 'Y' TO WS-EOF-FLAG NOT AT END ADD 1 TO WS-RECORD-COUNT PERFORM PROCESS-RECORD END-READ END-PERFORM. PROCESS-RECORD. MOVE CUSTOMER-NAME TO REPORT-LINE WRITE REPORT-LINE. FINALIZATION. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE DISPLAY "Processed " WS-RECORD-COUNT " records".

The PROCEDURE DIVISION is organized into logical paragraphs that group related operations together.

Paragraphs and Sections

The PROCEDURE DIVISION uses two levels of organization:

  • Paragraphs - Named groups of statements (e.g., MAIN-PROCESS, INITIALIZATION)
  • Sections - Named groups of paragraphs (optional, used for complex programs)
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
PROCEDURE DIVISION. FILE-PROCESSING SECTION. INITIALIZATION. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE. DATA-PROCESSING SECTION. MAIN-PROCESS. PERFORM PROCESS-RECORDS UNTIL END-OF-FILE. PROCESS-RECORDS. READ CUSTOMER-FILE PERFORM CALCULATE-TOTALS. CALCULATE-TOTALS. ADD CUSTOMER-AMOUNT TO WS-TOTAL. FINALIZATION SECTION. CLEANUP. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE.

Common Statement Types

The PROCEDURE DIVISION contains various types of executable statements:

Statement TypePurposeExample
File OperationsOpen, read, write, close filesOPEN INPUT CUSTOMER-FILE
Data MovementMove data between fieldsMOVE CUSTOMER-NAME TO WS-NAME
ArithmeticPerform calculationsADD AMOUNT TO TOTAL
Control FlowConditional and loop logicIF AMOUNT > 1000
Program ControlCall other programsCALL "SUBPROGRAM"

Program Flow

A typical COBOL program follows this general flow:

  1. Initialization - Set up program environment, open files, initialize variables
  2. Main Processing - Perform the primary program logic
  3. Cleanup - Close files, display results, perform final operations
  4. Termination - End the program with STOP RUN

Complete Program Examples

These examples demonstrate complete COBOL programs with all four divisions properly structured and organized.

Example 1: Simple Hello World Program

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
IDENTIFICATION DIVISION. PROGRAM-ID. HELLO-WORLD. AUTHOR. JOHN DOE. DATE-WRITTEN. 12/31/2023. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-3090. OBJECT-COMPUTER. IBM-3090. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-MESSAGE PIC X(20) VALUE "Hello, World!". PROCEDURE DIVISION. MAIN-PROCESS. DISPLAY WS-MESSAGE STOP RUN.

This minimal program demonstrates the basic structure with all required divisions.

Example 2: File Processing Program

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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESSING. AUTHOR. JANE SMITH. DATE-WRITTEN. 12/31/2023. REMARKS. This program processes customer records. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-STATUS. SELECT REPORT-FILE ASSIGN TO "REPORT.TXT" ORGANIZATION IS LINE SEQUENTIAL FILE STATUS IS REPORT-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(45). WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 REPORT-STATUS PIC XX. 01 WS-RECORD-COUNT PIC 9(5) VALUE 0. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening customer file: " CUSTOMER-STATUS STOP RUN END-IF. PROCESS-RECORDS. PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE 'Y' TO WS-EOF-FLAG NOT AT END ADD 1 TO WS-RECORD-COUNT PERFORM WRITE-REPORT-LINE END-READ END-PERFORM. WRITE-REPORT-LINE. MOVE CUSTOMER-NAME TO REPORT-LINE WRITE REPORT-LINE. FINALIZATION. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE DISPLAY "Processed " WS-RECORD-COUNT " customer records".

This program demonstrates file processing with proper error handling and structured program flow.

Example 3: Subprogram with Parameters

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
IDENTIFICATION DIVISION. PROGRAM-ID. CALCULATE-TAX. AUTHOR. BOB JOHNSON. DATE-WRITTEN. 12/31/2023. REMARKS. Subprogram to calculate tax amount. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-3090. OBJECT-COMPUTER. IBM-3090. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-TAX-RATE PIC V999 VALUE .08. LINKAGE SECTION. 01 LS-AMOUNT PIC 9(7)V99. 01 LS-TAX-AMOUNT PIC 9(7)V99. 01 LS-RETURN-CODE PIC 9(2). PROCEDURE DIVISION USING LS-AMOUNT, LS-TAX-AMOUNT, LS-RETURN-CODE. MAIN-PROCESS. PERFORM CALCULATE-TAX PERFORM SET-RETURN-CODE EXIT PROGRAM. CALCULATE-TAX. COMPUTE LS-TAX-AMOUNT = LS-AMOUNT * WS-TAX-RATE. SET-RETURN-CODE. MOVE 0 TO LS-RETURN-CODE.

This subprogram demonstrates the use of the LINKAGE SECTION for parameter passing.

Best Practices and Guidelines

Following these best practices ensures well-structured, maintainable COBOL programs.

Division Organization

  • Always include all four divisions in the correct order
  • Use meaningful program names that clearly identify the program's purpose
  • Include documentation paragraphs in the IDENTIFICATION DIVISION
  • Organize DATA DIVISION sections logically (FILE, WORKING-STORAGE, LINKAGE)
  • Structure PROCEDURE DIVISION with clear, descriptive paragraph names

Naming Conventions

  • Use descriptive names for programs, variables, and paragraphs
  • Follow consistent prefixes (WS- for working storage, LS- for linkage)
  • Use hyphens to separate words in COBOL names
  • Avoid reserved words when naming data items
  • Keep names reasonably short but descriptive

Program Structure

  • Organize paragraphs logically (initialization, main processing, cleanup)
  • Use PERFORM statements to call paragraphs and maintain structure
  • Include error handling for file operations and data validation
  • Add comments to explain complex logic or business rules
  • Keep paragraphs focused on a single responsibility

Common Pitfalls to Avoid

  • Missing PROGRAM-ID in the IDENTIFICATION DIVISION
  • Incorrect division order - divisions must appear in the specified sequence
  • Undefined data items - all variables must be defined before use
  • Missing STOP RUN - programs should have a clear termination point
  • Poor paragraph organization - unclear program flow and structure
  • Inconsistent naming - makes programs difficult to maintain

Test Your Knowledge

1. What are the four main divisions of a COBOL program?

  • IDENTIFICATION, ENVIRONMENT, DATA, PROCEDURE
  • HEADER, BODY, FOOTER, MAIN
  • DECLARATION, INITIALIZATION, PROCESSING, TERMINATION
  • PROGRAM, FILE, WORKING, LOGIC

2. Which division contains the actual program logic and executable statements?

  • IDENTIFICATION DIVISION
  • ENVIRONMENT DIVISION
  • DATA DIVISION
  • PROCEDURE DIVISION

3. What is the purpose of the ENVIRONMENT DIVISION?

  • To define program variables
  • To specify hardware and software dependencies
  • To contain program logic
  • To identify the program

4. Which section of the DATA DIVISION is required in all COBOL programs?

  • FILE SECTION
  • WORKING-STORAGE SECTION
  • LINKAGE SECTION
  • None of the above

5. What is the minimum required entry in the IDENTIFICATION DIVISION?

  • PROGRAM-ID
  • AUTHOR
  • DATE-WRITTEN
  • All of the above

Frequently Asked Questions