COBOL DIVISION Structure
Master COBOL program organization through the four fundamental divisions that provide structure, clarity, and maintainability to mainframe applications.
Overview
COBOL programs are organized into four main divisions, each serving a specific purpose in program structure and functionality. This divisional structure is fundamental to COBOL's design philosophy, promoting clear separation of concerns and making programs more readable, maintainable, and standardized across different implementations.
The division structure reflects COBOL's business-oriented design, where each division addresses different aspects of a business application: program identification, environmental considerations, data organization, and processing logic. Understanding this structure is essential for writing well-organized COBOL programs.
Each division follows specific rules for content, organization, and sequence. The divisions must appear in a prescribed order, and each contains sections and paragraphs that further organize the program's components. This hierarchical structure ensures consistency and predictability in COBOL program organization.
The Four COBOL Divisions
1. IDENTIFICATION DIVISION
The IDENTIFICATION DIVISION provides program identification and documentation information:
1234567IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-REPORT. AUTHOR. DEVELOPMENT TEAM. INSTALLATION. CORPORATE DATA CENTER. DATE-WRITTEN. 2024-01-15. DATE-COMPILED. SECURITY. CONFIDENTIAL.
This division is required in every COBOL program and must be the first division. It contains metadata about the program including its name, author, creation date, and security classification.
2. ENVIRONMENT DIVISION
The ENVIRONMENT DIVISION specifies the computer environment and file assignments:
123456789101112ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-Z15. OBJECT-COMPUTER. IBM-Z15. SPECIAL-NAMES. DECIMAL-POINT IS COMMA. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL.
This division is optional but commonly used. It defines the computing environment, file assignments, and special system configurations needed for the program.
3. DATA DIVISION
The DATA DIVISION defines all data structures and storage areas:
123456789101112DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUST-ID PIC X(10). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(7)V99. WORKING-STORAGE SECTION. 01 WS-COUNTERS. 05 WS-RECORD-COUNT PIC 9(5) VALUE ZERO. 05 WS-TOTAL-AMOUNT PIC 9(9)V99 VALUE ZERO.
This division is optional but used in most programs. It defines file structures, working storage variables, linkage parameters, and other data elements used by the program.
4. PROCEDURE DIVISION
The PROCEDURE DIVISION contains the executable logic and processing instructions:
1234567891011121314151617181920PROCEDURE DIVISION. MAIN-LOGIC. PERFORM INITIALIZATION PERFORM PROCESS-CUSTOMERS PERFORM FINALIZATION GOBACK. INITIALIZATION. OPEN INPUT CUSTOMER-FILE DISPLAY "Customer Report Started". PROCESS-CUSTOMERS. PERFORM UNTIL WS-EOF = "Y" READ CUSTOMER-FILE AT END MOVE "Y" TO WS-EOF NOT AT END PERFORM PROCESS-CUSTOMER-RECORD END-READ END-PERFORM.
This division is required and contains all the executable statements that define what the program does. It's organized into sections, paragraphs, and sentences.
Division Organization and Structure
Hierarchical Structure
COBOL programs follow a strict hierarchical structure within divisions:
12345678DIVISION-NAME DIVISION. SECTION-NAME SECTION. PARAGRAPH-NAME. SENTENCE. SENTENCE. ANOTHER-PARAGRAPH. SENTENCE.
Each division can contain sections, which contain paragraphs, which contain sentences. This hierarchy provides multiple levels of organization for complex programs.
Section Usage
Sections provide logical groupings within divisions:
12345678910111213141516DATA DIVISION. FILE SECTION. * File definitions go here WORKING-STORAGE SECTION. * Working variables go here LINKAGE SECTION. * Parameters go here PROCEDURE DIVISION. INITIALIZATION SECTION. * Startup logic goes here MAIN-PROCESSING SECTION. * Main business logic goes here
Sections help organize related functionality and make programs more maintainable and readable.
Complete Program Example
Customer Processing Program
Here's a complete COBOL program demonstrating all four divisions:
1234567891011121314151617181920212223242526272829303132333435363738394041424344IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROCESSOR. AUTHOR. COBOL DEVELOPMENT TEAM. DATE-WRITTEN. 2024-01-15. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-MAINFRAME. OBJECT-COMPUTER. IBM-MAINFRAME. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-INPUT ASSIGN TO "CUSTINP" ORGANIZATION IS SEQUENTIAL. SELECT REPORT-OUTPUT ASSIGN TO "CUSTRPT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD CUSTOMER-INPUT. 01 CUSTOMER-RECORD. 05 CUST-ID PIC X(5). 05 CUST-NAME PIC X(25). 05 CUST-BALANCE PIC 9(7)V99. FD REPORT-OUTPUT. 01 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-FLAGS. 05 WS-EOF PIC X(1) VALUE "N". 01 WS-COUNTERS. 05 WS-RECORD-COUNT PIC 9(5) VALUE ZERO. 05 WS-TOTAL-BALANCE PIC 9(9)V99 VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. PERFORM OPEN-FILES PERFORM PROCESS-RECORDS PERFORM CLOSE-FILES GOBACK.
This example shows how all four divisions work together to create a complete, functional COBOL program.
Advanced Division Concepts
Nested Programs
COBOL supports nested programs, where each nested program has its own divisions:
123456789101112131415161718192021222324IDENTIFICATION DIVISION. PROGRAM-ID. MAIN-PROGRAM. * Main program divisions... PROCEDURE DIVISION. MAIN-LOGIC. CALL "UTILITY-PROGRAM" GOBACK. * Nested program starts here IDENTIFICATION DIVISION. PROGRAM-ID. UTILITY-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-UTILITY-DATA PIC X(100). PROCEDURE DIVISION. DISPLAY "Utility program executing" GOBACK. END PROGRAM UTILITY-PROGRAM. END PROGRAM MAIN-PROGRAM.
Nested programs allow for modular design while keeping related functionality together.
Division Headers and Documentation
Good practice includes comprehensive documentation within divisions:
123456789101112IDENTIFICATION DIVISION. PROGRAM-ID. PAYROLL-PROCESSOR. AUTHOR. PAYROLL SYSTEMS TEAM. INSTALLATION. CORPORATE DATA CENTER. DATE-WRITTEN. 2024-01-15. DATE-COMPILED. SECURITY. PAYROLL-CONFIDENTIAL. REMARKS. THIS PROGRAM PROCESSES WEEKLY PAYROLL DATA AND GENERATES PAYROLL REPORTS AND CHECKS. MODIFIED: 2024-01-20 - ADDED OVERTIME CALCULATION MODIFIED: 2024-01-25 - ENHANCED ERROR HANDLING.
Comprehensive documentation in the IDENTIFICATION DIVISION helps with program maintenance and understanding.
Best Practices for Division Organization
Structural Guidelines
Follow these best practices for organizing divisions:
- Always include comprehensive IDENTIFICATION DIVISION documentation
- Use meaningful section names that describe their purpose
- Organize paragraphs logically within the PROCEDURE DIVISION
- Keep related data definitions together in the DATA DIVISION
- Use consistent naming conventions across all divisions
- Include comments to explain complex logic or business rules
Maintainability Considerations
Structure divisions for long-term maintainability:
12345678910111213141516171819PROCEDURE DIVISION. * Main control logic 0000-MAIN-CONTROL. PERFORM 1000-INITIALIZATION PERFORM 2000-MAIN-PROCESSING PERFORM 3000-FINALIZATION GOBACK. * Initialization routines 1000-INITIALIZATION. PERFORM 1100-OPEN-FILES PERFORM 1200-INITIALIZE-VARIABLES PERFORM 1300-VALIDATE-PARAMETERS. * Main processing logic 2000-MAIN-PROCESSING. PERFORM 2100-READ-INPUT PERFORM 2200-PROCESS-RECORDS PERFORM 2300-GENERATE-REPORTS.
Using numbered paragraph names and logical groupings makes programs easier to navigate and maintain.
Common Division Patterns
Batch Processing Pattern
Common structure for batch processing programs:
123456789101112131415161718192021222324PROCEDURE DIVISION. MAIN-LOGIC. PERFORM HOUSEKEEPING PERFORM PROCESS-DATA UNTIL END-OF-FILE PERFORM WRAP-UP GOBACK. HOUSEKEEPING. OPEN INPUT INPUT-FILE OPEN OUTPUT OUTPUT-FILE READ INPUT-FILE AT END MOVE "Y" TO EOF-FLAG END-READ. PROCESS-DATA. PERFORM BUSINESS-LOGIC READ INPUT-FILE AT END MOVE "Y" TO EOF-FLAG END-READ. WRAP-UP. CLOSE INPUT-FILE CLOSE OUTPUT-FILE DISPLAY "Processing complete".
This pattern separates initialization, processing, and cleanup into distinct sections.
Interactive Program Pattern
Structure for interactive or menu-driven programs:
12345678910111213141516171819202122232425PROCEDURE DIVISION. MAIN-MENU. PERFORM DISPLAY-MENU PERFORM GET-USER-CHOICE PERFORM PROCESS-CHOICE IF NOT END-SESSION GO TO MAIN-MENU END-IF GOBACK. DISPLAY-MENU. DISPLAY "1. Add Customer" DISPLAY "2. Update Customer" DISPLAY "3. Delete Customer" DISPLAY "4. Exit" DISPLAY "Enter choice: " WITH NO ADVANCING. PROCESS-CHOICE. EVALUATE USER-CHOICE WHEN "1" PERFORM ADD-CUSTOMER WHEN "2" PERFORM UPDATE-CUSTOMER WHEN "3" PERFORM DELETE-CUSTOMER WHEN "4" MOVE "Y" TO END-SESSION-FLAG WHEN OTHER DISPLAY "Invalid choice" END-EVALUATE.
Interactive programs benefit from clear menu structures and user input validation.
Hands-on Exercise
Exercise: Employee Report Program
Create a complete COBOL program using all four divisions to process employee data and generate a summary report.
Requirements:
- Include all four divisions with proper documentation
- Define file structures for employee input and report output
- Implement proper program organization with sections and paragraphs
- Include error handling and summary statistics
- Follow COBOL naming conventions and best practices
View Solution
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108IDENTIFICATION DIVISION. PROGRAM-ID. EMPLOYEE-REPORT. AUTHOR. COBOL TUTORIAL TEAM. DATE-WRITTEN. 2024-01-15. REMARKS. PROCESSES EMPLOYEE DATA AND GENERATES SUMMARY REPORT. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-MAINFRAME. OBJECT-COMPUTER. IBM-MAINFRAME. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO "EMPLOYEE.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS WS-FILE-STATUS. SELECT REPORT-FILE ASSIGN TO "EMPREPORT.TXT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMP-ID PIC X(5). 05 EMP-NAME PIC X(25). 05 EMP-DEPT PIC X(10). 05 EMP-SALARY PIC 9(6)V99. FD REPORT-FILE. 01 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-FLAGS. 05 WS-EOF PIC X(1) VALUE "N". 05 WS-FILE-STATUS PIC X(2). 01 WS-COUNTERS. 05 WS-EMP-COUNT PIC 9(4) VALUE ZERO. 05 WS-TOTAL-SALARY PIC 9(8)V99 VALUE ZERO. 05 WS-AVG-SALARY PIC 9(6)V99 VALUE ZERO. 01 WS-REPORT-LINES. 05 WS-HEADER-LINE PIC X(80) VALUE "EMPLOYEE SUMMARY REPORT". 05 WS-DETAIL-LINE. 10 FILLER PIC X(5) VALUE SPACES. 10 WS-RPT-ID PIC X(5). 10 FILLER PIC X(3) VALUE SPACES. 10 WS-RPT-NAME PIC X(25). 10 FILLER PIC X(3) VALUE SPACES. 10 WS-RPT-DEPT PIC X(10). 10 FILLER PIC X(3) VALUE SPACES. 10 WS-RPT-SAL PIC Z,ZZZ,ZZ9.99. PROCEDURE DIVISION. 0000-MAIN-CONTROL. PERFORM 1000-INITIALIZATION PERFORM 2000-PROCESS-EMPLOYEES PERFORM 3000-FINALIZATION GOBACK. 1000-INITIALIZATION. OPEN INPUT EMPLOYEE-FILE OPEN OUTPUT REPORT-FILE WRITE REPORT-LINE FROM WS-HEADER-LINE PERFORM 1100-READ-EMPLOYEE. 1100-READ-EMPLOYEE. READ EMPLOYEE-FILE AT END MOVE "Y" TO WS-EOF NOT AT END ADD 1 TO WS-EMP-COUNT ADD EMP-SALARY TO WS-TOTAL-SALARY END-READ. 2000-PROCESS-EMPLOYEES. PERFORM UNTIL WS-EOF = "Y" PERFORM 2100-FORMAT-DETAIL-LINE WRITE REPORT-LINE FROM WS-DETAIL-LINE PERFORM 1100-READ-EMPLOYEE END-PERFORM. 2100-FORMAT-DETAIL-LINE. MOVE EMP-ID TO WS-RPT-ID MOVE EMP-NAME TO WS-RPT-NAME MOVE EMP-DEPT TO WS-RPT-DEPT MOVE EMP-SALARY TO WS-RPT-SAL. 3000-FINALIZATION. IF WS-EMP-COUNT > ZERO COMPUTE WS-AVG-SALARY = WS-TOTAL-SALARY / WS-EMP-COUNT END-IF PERFORM 3100-WRITE-SUMMARY CLOSE EMPLOYEE-FILE CLOSE REPORT-FILE. 3100-WRITE-SUMMARY. MOVE SPACES TO REPORT-LINE WRITE REPORT-LINE STRING "TOTAL EMPLOYEES: " WS-EMP-COUNT INTO REPORT-LINE WRITE REPORT-LINE STRING "AVERAGE SALARY: " WS-AVG-SALARY INTO REPORT-LINE WRITE REPORT-LINE.
Quiz
Test Your Knowledge
1. What is the correct order of COBOL divisions?
2. Which divisions are required in every COBOL program?
3. What is the primary purpose of the DATA DIVISION?
View Answers
1. IDENTIFICATION, ENVIRONMENT, DATA, PROCEDURE - This is the required order that cannot be changed in COBOL programs.
2. IDENTIFICATION and PROCEDURE only - These are the only two divisions that must be present in every COBOL program.
3. Defines data structures and storage - The DATA DIVISION defines all data elements, file structures, and storage areas used by the program.
Frequently Asked Questions
Related Pages
Related Concepts
Program Structure
Understanding COBOL program organization and hierarchical structure
Modular Programming
Organizing code into logical divisions and sections for maintainability
COBOL Basics
Fundamental concepts of COBOL programming and structure
Documentation Standards
Best practices for documenting and organizing COBOL programs