MainframeMaster

COBOL Tutorial

PROCEDURE DIVISION Structure

Progress0 of 0 lessons

PROCEDURE DIVISION Header

The PROCEDURE DIVISION is the fourth and final division in a COBOL program. It contains all the executable statements that perform the actual work of the program. This division is where the business logic is implemented through various COBOL statements and commands.

Basic Format

cobol
1
2
PROCEDURE DIVISION. executable statements...

The simplest form with no parameters or return value.

With Parameters

cobol
1
2
PROCEDURE DIVISION USING parameter-1 [parameter-2 ...]. executable statements...

Used when the program receives parameters from a calling program. The parameters must be defined in the LINKAGE SECTION.

With Return Value

cobol
1
2
PROCEDURE DIVISION RETURNING return-item. executable statements...

Used when the program returns a value to the calling program.

With Both Parameters and Return Value

cobol
1
2
3
PROCEDURE DIVISION USING parameter-1 [parameter-2 ...] RETURNING return-item. executable statements...

Used when the program both receives parameters and returns a value.

Sections and Paragraphs

The PROCEDURE DIVISION is typically organized into sections and paragraphs. These organizational units help structure the code and make it more readable and maintainable.

Sections

  • A section is identified by a name followed by the word SECTION and a period
  • Sections are optional in modern COBOL
  • Used for logical grouping of paragraphs
  • Can be referenced by the PERFORM statement
cobol
1
2
3
4
5
MAIN-LOGIC SECTION. PERFORM INITIALIZATION. PERFORM PROCESS-DATA UNTIL END-OF-FILE. PERFORM CLEAN-UP. STOP RUN.

Paragraphs

  • A paragraph is identified by a name followed by a period
  • Contains one or more sentences
  • Focuses on a specific task or function
  • Can be referenced by the PERFORM statement
cobol
1
2
3
4
5
6
INITIALIZATION. OPEN INPUT CUSTOMER-FILE. OPEN OUTPUT REPORT-FILE. READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ.

Typical Organizational 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
39
40
41
42
43
PROCEDURE DIVISION. MAIN-CONTROL SECTION. MAIN-PARAGRAPH. PERFORM INITIALIZATION. PERFORM PROCESS-RECORDS UNTIL END-OF-FILE. PERFORM TERMINATION. STOP RUN. FILE-HANDLING SECTION. INITIALIZATION. OPEN INPUT DATA-FILE. OPEN OUTPUT REPORT-FILE. PERFORM READ-RECORD. READ-RECORD. READ DATA-FILE AT END SET END-OF-FILE TO TRUE END-READ. TERMINATION. CLOSE DATA-FILE. CLOSE REPORT-FILE. DATA-PROCESSING SECTION. PROCESS-RECORDS. PERFORM PROCESS-CURRENT-RECORD. PERFORM READ-RECORD. PROCESS-CURRENT-RECORD. IF RECORD-TYPE = "CUSTOMER" PERFORM PROCESS-CUSTOMER ELSE PERFORM PROCESS-ORDER END-IF. PROCESS-CUSTOMER. MOVE CUSTOMER-ID TO REPORT-CUSTOMER-ID. MOVE CUSTOMER-NAME TO REPORT-CUSTOMER-NAME. WRITE REPORT-RECORD. PROCESS-ORDER. ADD ORDER-AMOUNT TO TOTAL-ORDERS. WRITE REPORT-RECORD.

This example shows a typical PROCEDURE DIVISION organized into sections and paragraphs, with a clear flow of control.

Sentences and Statements

Within paragraphs, COBOL code is organized into sentences and statements. Understanding these elements is crucial for writing and reading COBOL code effectively.

Sentences

  • A sentence is one or more statements terminated by a period
  • The period acts as a sentence terminator
  • Multiple statements in a sentence are executed sequentially
cobol
1
2
3
4
5
READ CUSTOMER-FILE. *> This is a sentence with one statement MOVE CUSTOMER-NAME TO REPORT-NAME ADD 1 TO RECORD-COUNT. *> This is a sentence with two statements

Statements

  • A statement is a COBOL verb followed by its operands
  • Represents a single operation or instruction
  • Examples: MOVE, READ, WRITE, ADD, IF, PERFORM
cobol
1
2
3
4
MOVE SPACES TO CUSTOMER-NAME. READ CUSTOMER-FILE. ADD ITEM-AMOUNT TO TOTAL-AMOUNT. IF AMOUNT > 1000 PERFORM PROCESS-LARGE-ORDER.

Scope Terminators

Modern COBOL uses scope terminators to clearly indicate the end of statements, especially for nested statements. This improves code readability and reduces errors caused by ambiguous statement boundaries.

Common Scope Terminators

  • END-IF
  • END-READ
  • END-WRITE
  • END-PERFORM
  • END-EVALUATE
  • END-STRING
  • END-UNSTRING
  • END-SEARCH
  • END-COMPUTE
  • END-CALL

Benefits of Scope Terminators

  • Improves readability, especially for nested statements
  • Reduces ambiguity and errors
  • Makes complex conditions easier to follow
  • Allows sentences to contain multiple structured statements
  • Supports modern structured programming techniques

Without Scope Terminators (Older Style)

cobol
1
2
3
4
5
6
IF AMOUNT > 1000 IF CUSTOMER-TYPE = "PREMIUM" MULTIPLY AMOUNT BY 0.90 MOVE "DISCOUNT APPLIED" TO REPORT-MESSAGE ELSE MOVE "NO DISCOUNT" TO REPORT-MESSAGE.

Without scope terminators, it's not immediately clear which IF statement the ELSE belongs to.

With Scope Terminators (Modern Style)

cobol
1
2
3
4
5
6
7
8
IF AMOUNT > 1000 IF CUSTOMER-TYPE = "PREMIUM" MULTIPLY AMOUNT BY 0.90 MOVE "DISCOUNT APPLIED" TO REPORT-MESSAGE ELSE MOVE "NO DISCOUNT" TO REPORT-MESSAGE END-IF END-IF.

With scope terminators, the structure is clear and unambiguous.

Program Organization Strategies

Well-organized COBOL programs are easier to understand, maintain, and enhance. There are several strategies for organizing the PROCEDURE DIVISION effectively.

Top-Down Organization

  • Start with a main control paragraph that outlines the program flow
  • Use PERFORM statements to call more detailed paragraphs
  • Break complex tasks into smaller, focused paragraphs
  • Create a hierarchical structure that flows from general to specific
cobol
1
2
3
4
5
MAIN-CONTROL. PERFORM INITIALIZATION. PERFORM PROCESS-DATA UNTIL END-OF-FILE. PERFORM FINALIZATION. STOP RUN.

Functional Organization

  • Group paragraphs by function or purpose
  • Use sections to categorize related paragraphs
  • Create clear boundaries between different functional areas
  • Makes code more modular and maintainable
cobol
1
2
3
4
5
6
7
8
FILE-HANDLING SECTION. file handling paragraphs... DATA-VALIDATION SECTION. data validation paragraphs... REPORT-GENERATION SECTION. report generation paragraphs...

Modern Modular Approach

  • Break large programs into subprograms using the CALL statement
  • Each subprogram handles a specific function
  • Use the LINKAGE SECTION for parameter passing
  • Enables code reuse and easier maintenance
cobol
1
2
3
4
5
6
MAIN-PROGRAM SECTION. MAIN-CONTROL. CALL "INITIALIZE-FILES" USING FILE-STATUS. CALL "PROCESS-RECORDS" USING CUSTOMER-FILE, REPORT-FILE. CALL "GENERATE-SUMMARY" USING REPORT-FILE, SUMMARY-COUNTS. STOP RUN.

Exercise: Analyzing and Creating PROCEDURE DIVISION Code

Practice analyzing and creating PROCEDURE DIVISION code with the following exercise:

Exercise 1: Analyze the Structure

Identify the sections, paragraphs, sentences, and statements in the following PROCEDURE DIVISION code:

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
PROCEDURE DIVISION. MAIN-LOGIC SECTION. MAIN-PARAGRAPH. OPEN INPUT CUSTOMER-FILE. OPEN OUTPUT REPORT-FILE. READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ. PERFORM UNTIL END-OF-FILE PERFORM PROCESS-CUSTOMER READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ END-PERFORM. PERFORM WRAP-UP. STOP RUN. PROCESS-CUSTOMER. IF CUSTOMER-STATUS = "A" MOVE CUSTOMER-ID TO REPORT-ID MOVE CUSTOMER-NAME TO REPORT-NAME WRITE REPORT-RECORD END-IF. WRAP-UP. CLOSE CUSTOMER-FILE. CLOSE REPORT-FILE. DISPLAY "Processing complete".

Exercise 2: Refactor the Code

Refactor the following code to use modern structured programming with scope terminators:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
PROCEDURE DIVISION. PROCESS-PARAGRAPH. OPEN INPUT DATA-FILE. READ DATA-FILE AT END MOVE "Y" TO EOF-FLAG. PERFORM UNTIL EOF-FLAG = "Y" IF RECORD-TYPE = "C" MOVE CUST-NAME TO OUTPUT-NAME IF CUST-BALANCE > 1000 MOVE "HIGH BALANCE" TO OUTPUT-MESSAGE ELSE MOVE "NORMAL" TO OUTPUT-MESSAGE WRITE OUTPUT-RECORD ELSE IF RECORD-TYPE = "O" ADD ORDER-AMOUNT TO TOTAL-ORDERS. READ DATA-FILE AT END MOVE "Y" TO EOF-FLAG. CLOSE DATA-FILE. STOP RUN.

Exercise 3: Create Your Own

Write a PROCEDURE DIVISION for a program that reads a customer file and categorizes customers into three groups based on their account balance:

  • Premium: Balance greater than $10,000
  • Standard: Balance between $1,000 and $10,000
  • Basic: Balance less than $1,000

The program should create a report file with customer details and their category, and at the end, display the count of customers in each category.

Best Practices for PROCEDURE DIVISION

Structure and Organization

  • Use a logical, top-down organization
  • Create a clear main control paragraph
  • Group related functions into sections
  • Keep paragraphs focused on single tasks
  • Use meaningful names for sections and paragraphs

Coding Style

  • Always use scope terminators for structured statements
  • Indent code to show logical hierarchy
  • Avoid GO TO statements when possible
  • Use in-line PERFORM for simple operations
  • Keep sentences simple and focused

Modularization

  • Break complex processes into smaller paragraphs
  • Consider using subprograms for major functions
  • Create reusable code when possible
  • Limit paragraph size for better readability
  • Use the CALL statement for code reuse

Documentation

  • Add comments to explain complex logic
  • Document the purpose of each section and paragraph
  • Use clear, descriptive names
  • Comment any unusual or non-obvious code
  • Include version history in comments

Test Your Knowledge

1. What is the main purpose of the PROCEDURE DIVISION in a COBOL program?

  • To define program variables and constants
  • To establish file connections to the operating system
  • To contain executable instructions and business logic
  • To identify the program and its author

2. Which of the following is the correct hierarchical order in the PROCEDURE DIVISION (from highest to lowest)?

  • Section → Paragraph → Sentence → Statement
  • Paragraph → Section → Statement → Sentence
  • Statement → Sentence → Paragraph → Section
  • Sentence → Statement → Section → Paragraph

3. What is the purpose of scope terminators in COBOL?

  • To end a program execution
  • To indicate the end of nested statements and improve readability
  • To terminate a section or paragraph
  • To close files before program completion

4. Which of the following is NOT a valid PROCEDURE DIVISION header format?

  • PROCEDURE DIVISION.
  • PROCEDURE DIVISION USING CUSTOMER-RECORD.
  • PROCEDURE DIVISION RETURNING ORDER-STATUS.
  • PROCEDURE DIVISION DEFINING MAIN-PROCESS.

5. What statement is typically used to transfer control to a paragraph in the PROCEDURE DIVISION?

  • GOTO paragraph-name
  • PERFORM paragraph-name
  • CALL paragraph-name
  • EXECUTE paragraph-name

Frequently Asked Questions