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.
COBOL programs are organized into four distinct divisions, each serving a specific purpose:
These divisions must appear in this exact order, and each division has specific rules about what can be included within it.
12345678910111213141516IDENTIFICATION 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 | Required | Purpose | Content |
---|---|---|---|
IDENTIFICATION | Yes | Program identification | PROGRAM-ID, documentation |
ENVIRONMENT | Yes | System configuration | Hardware, software, files |
DATA | Yes | Data definitions | Variables, files, records |
PROCEDURE | Yes | Program logic | Executable statements |
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.
The IDENTIFICATION DIVISION contains one required paragraph and several optional ones:
1234567IDENTIFICATION 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.
The PROGRAM-ID paragraph is mandatory and specifies the program name:
12345678* 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.
Optional paragraphs provide additional documentation:
Paragraph | Purpose | Example |
---|---|---|
AUTHOR | Program author | AUTHOR. JOHN DOE. |
DATE-WRITTEN | Creation date | DATE-WRITTEN. 12/31/2023. |
DATE-COMPILED | Compilation date | DATE-COMPILED. 01/15/2024. |
SECURITY | Security level | SECURITY. CONFIDENTIAL. |
REMARKS | Additional notes | REMARKS. Customer data processing. |
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.
The ENVIRONMENT DIVISION consists of two main sections:
123456789101112ENVIRONMENT 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.
This section contains three main paragraphs:
Paragraph | Purpose | Example |
---|---|---|
SOURCE-COMPUTER | Development environment | SOURCE-COMPUTER. IBM-3090. |
OBJECT-COMPUTER | Execution environment | OBJECT-COMPUTER. IBM-3090. |
SPECIAL-NAMES | System-specific names | CURRENCY SIGN IS "$". |
This section handles file and I/O configurations:
123456789101112131415INPUT-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.
In contemporary COBOL environments, the ENVIRONMENT DIVISION is often simplified:
1234ENVIRONMENT 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.
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.
The DATA DIVISION consists of three main sections:
123456789101112131415161718DATA 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.
The FILE SECTION defines external file structures:
The FILE SECTION is required only when the program processes files. Each file used by the program must have a corresponding FD entry.
The WORKING-STORAGE SECTION defines internal program variables:
123456789101112131415161718192021WORKING-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.
The LINKAGE SECTION defines parameters passed between programs:
1234567891011121314LINKAGE 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 | Required | When Used |
---|---|---|
FILE SECTION | No | When processing files |
WORKING-STORAGE SECTION | No | When using variables |
LINKAGE SECTION | No | When receiving parameters |
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.
The PROCEDURE DIVISION consists of paragraphs and sections:
12345678910111213141516171819202122232425262728293031PROCEDURE 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.
The PROCEDURE DIVISION uses two levels of organization:
123456789101112131415161718192021PROCEDURE 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.
The PROCEDURE DIVISION contains various types of executable statements:
Statement Type | Purpose | Example |
---|---|---|
File Operations | Open, read, write, close files | OPEN INPUT CUSTOMER-FILE |
Data Movement | Move data between fields | MOVE CUSTOMER-NAME TO WS-NAME |
Arithmetic | Perform calculations | ADD AMOUNT TO TOTAL |
Control Flow | Conditional and loop logic | IF AMOUNT > 1000 |
Program Control | Call other programs | CALL "SUBPROGRAM" |
A typical COBOL program follows this general flow:
These examples demonstrate complete COBOL programs with all four divisions properly structured and organized.
123456789101112131415161718IDENTIFICATION 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.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869IDENTIFICATION 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.
12345678910111213141516171819202122232425262728293031IDENTIFICATION 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.
Following these best practices ensures well-structured, maintainable COBOL programs.
1. What are the four main divisions of a COBOL program?
2. Which division contains the actual program logic and executable statements?
3. What is the purpose of the ENVIRONMENT DIVISION?
4. Which section of the DATA DIVISION is required in all COBOL programs?
5. What is the minimum required entry in the IDENTIFICATION DIVISION?
Detailed coverage of the IDENTIFICATION DIVISION and its paragraphs.
Understanding the ENVIRONMENT DIVISION and system configuration.
Overview of all sections in the DATA DIVISION.
Understanding program logic and executable statements.
How files are described in the DATA DIVISION.