MainframeMaster

COBOL Tutorial

COBOL Structured Programming

Progress0 of 0 lessons

Introduction to Structured Programming

Structured programming is a programming paradigm that emphasizes the use of clear, logical control structures and modular design. In COBOL, structured programming principles help create programs that are easier to understand, debug, test, and maintain.

What is Structured Programming?

Structured programming is a methodology that uses:

  • Clear control flow - Programs follow a logical, predictable path
  • Modular design - Code is organized into small, manageable units
  • Single entry/single exit - Each module has one entry and one exit point
  • Top-down design - Complex problems are broken into smaller parts
  • Avoidance of GOTO statements - Control flow is managed through structured constructs

These principles make programs more readable, maintainable, and less prone to errors.

Benefits of Structured Programming

BenefitDescriptionImpact
ReadabilityCode is easier to understand and followFaster development and debugging
MaintainabilityChanges can be made more easily and safelyReduced maintenance costs
TestabilityIndividual modules can be tested independentlyBetter quality assurance
ReusabilityModules can be reused in different programsIncreased productivity
ReliabilityStructured code is less prone to logical errorsFewer bugs and system failures

Three Basic Control Structures

Structured programming is built on three fundamental control structures: sequence, selection, and iteration. These structures can be combined to create any program logic.

1. Sequence Structure

Statements are executed in order, one after another:

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
PROCEDURE DIVISION. MAIN-PROCESS. * Sequence structure - statements execute in order PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE MOVE 0 TO RECORD-COUNT. PROCESS-DATA. READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO RECORD-COUNT PERFORM WRITE-REPORT-LINE END-READ. FINALIZATION. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE DISPLAY "Records processed: " RECORD-COUNT.

Each statement executes in sequence, creating a clear, predictable flow.

2. Selection Structure

Different code paths are executed based on conditions:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
PROCESS-CUSTOMER-RECORD. * Selection structure - different paths based on conditions IF CUSTOMER-TYPE = "PREMIUM" PERFORM PROCESS-PREMIUM-CUSTOMER ELSE IF CUSTOMER-TYPE = "STANDARD" PERFORM PROCESS-STANDARD-CUSTOMER ELSE PERFORM PROCESS-BASIC-CUSTOMER END-IF END-IF. PROCESS-PREMIUM-CUSTOMER. COMPUTE DISCOUNT = ORDER-AMOUNT * 0.15 MOVE "P" TO CUSTOMER-STATUS. PROCESS-STANDARD-CUSTOMER. COMPUTE DISCOUNT = ORDER-AMOUNT * 0.10 MOVE "S" TO CUSTOMER-STATUS. PROCESS-BASIC-CUSTOMER. COMPUTE DISCOUNT = ORDER-AMOUNT * 0.05 MOVE "B" TO CUSTOMER-STATUS.

IF-ELSE statements provide clear decision-making logic.

3. Iteration Structure

Code blocks are repeated based on conditions:

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
PROCESS-ALL-RECORDS. * Iteration structure - repeating operations PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END PERFORM PROCESS-CUSTOMER-RECORD ADD 1 TO RECORD-COUNT END-READ END-PERFORM. PROCESS-CUSTOMER-RECORDS-TIMES. * Iteration with counter PERFORM VARYING RECORD-NUMBER FROM 1 BY 1 UNTIL RECORD-NUMBER > MAX-RECORDS PERFORM PROCESS-SINGLE-RECORD END-PERFORM. PROCESS-CUSTOMER-RECORDS-WHILE. * Iteration with condition PERFORM WITH TEST BEFORE UNTIL RECORD-COUNT >= MAX-RECORDS PERFORM READ-NEXT-RECORD IF RECORD-VALID PERFORM PROCESS-VALID-RECORD END-IF END-PERFORM.

PERFORM statements provide various iteration patterns for different needs.

Control Structure Comparison

StructureCOBOL ImplementationUse CaseFlow
SequenceStatement orderLinear processingTop to bottom
SelectionIF-ELSE, EVALUATEDecision makingConditional branching
IterationPERFORM loopsRepeated operationsLooping

Modular Design with Paragraphs

Modular design breaks programs into smaller, manageable units called paragraphs. Each paragraph has a single, well-defined purpose and can be called independently.

Paragraph Definition and Usage

Paragraphs are named sections of code that can be called with PERFORM:

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. * Main program logic - calls other paragraphs PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. * Single purpose: Initialize program OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE MOVE 0 TO RECORD-COUNT MOVE "N" TO EOF-FLAG. PROCESS-DATA. * Single purpose: Process all records PERFORM UNTIL END-OF-FILE PERFORM READ-CUSTOMER-RECORD IF NOT END-OF-FILE PERFORM PROCESS-CUSTOMER-RECORD PERFORM WRITE-REPORT-LINE END-IF END-PERFORM. FINALIZATION. * Single purpose: Clean up and finish CLOSE CUSTOMER-FILE CLOSE REPORT-FILE DISPLAY "Processing complete" DISPLAY "Records processed: " RECORD-COUNT.

Each paragraph has a clear, single responsibility and can be tested independently.

Reusable Utility Paragraphs

Create utility paragraphs for common operations:

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
VALIDATE-CUSTOMER-DATA. * Reusable validation logic MOVE "Y" TO VALID-FLAG * Check customer ID IF CUSTOMER-ID = SPACES OR CUSTOMER-ID = ZEROS MOVE "N" TO VALID-FLAG MOVE "Invalid customer ID" TO ERROR-MESSAGE END-IF * Check customer name IF CUSTOMER-NAME = SPACES MOVE "N" TO VALID-FLAG MOVE "Customer name required" TO ERROR-MESSAGE END-IF * Check amount IF ORDER-AMOUNT <= 0 MOVE "N" TO VALID-FLAG MOVE "Invalid order amount" TO ERROR-MESSAGE END-IF. CALCULATE-DISCOUNT. * Reusable calculation logic EVALUATE CUSTOMER-TYPE WHEN "PREMIUM" COMPUTE DISCOUNT = ORDER-AMOUNT * 0.15 WHEN "STANDARD" COMPUTE DISCOUNT = ORDER-AMOUNT * 0.10 WHEN "BASIC" COMPUTE DISCOUNT = ORDER-AMOUNT * 0.05 WHEN OTHER MOVE 0 TO DISCOUNT END-EVALUATE. LOG-ERROR. * Reusable error logging ADD 1 TO ERROR-COUNT MOVE CURRENT-DATE TO ERROR-DATE MOVE CURRENT-TIME TO ERROR-TIME WRITE ERROR-RECORD FROM ERROR-LINE.

Utility paragraphs can be called from multiple places, reducing code duplication.

Paragraph Naming Conventions

  • Use descriptive names that indicate the paragraph's purpose
  • Use consistent prefixes for related paragraphs (e.g., VALIDATE-, PROCESS-, WRITE-)
  • Keep names concise but meaningful (30 characters or less)
  • Use hyphens to separate words for readability
  • Avoid abbreviations unless they are widely understood

Good Examples:

  • VALIDATE-CUSTOMER-DATA
  • PROCESS-TRANSACTION-RECORD
  • WRITE-REPORT-HEADER
  • CALCULATE-TOTAL-AMOUNT
  • HANDLE-FILE-ERROR

Sections and Higher-Level Organization

Sections provide a higher level of organization than paragraphs, allowing you to group related functionality together. They are useful for organizing large programs into logical divisions.

Section Definition and Usage

Sections contain multiple paragraphs and provide major program divisions:

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
PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION-SECTION PERFORM PROCESSING-SECTION PERFORM FINALIZATION-SECTION STOP RUN. INITIALIZATION-SECTION SECTION. * Section for all initialization activities OPEN-FILES. OPEN INPUT CUSTOMER-FILE OPEN OUTPUT REPORT-FILE OPEN OUTPUT ERROR-FILE. INITIALIZE-COUNTERS. MOVE 0 TO RECORD-COUNT MOVE 0 TO ERROR-COUNT MOVE "N" TO EOF-FLAG. WRITE-REPORT-HEADER. MOVE CURRENT-DATE TO REPORT-DATE MOVE CURRENT-TIME TO REPORT-TIME WRITE REPORT-RECORD FROM HEADER-LINE. PROCESSING-SECTION SECTION. * Section for main processing logic PROCESS-ALL-RECORDS. PERFORM UNTIL END-OF-FILE PERFORM READ-CUSTOMER-RECORD IF NOT END-OF-FILE PERFORM VALIDATE-CUSTOMER-RECORD IF VALID-RECORD PERFORM PROCESS-VALID-RECORD ELSE PERFORM LOG-INVALID-RECORD END-IF END-IF END-PERFORM. READ-CUSTOMER-RECORD. READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO RECORD-COUNT END-READ. VALIDATE-CUSTOMER-RECORD. PERFORM VALIDATE-CUSTOMER-DATA IF VALID-FLAG = "Y" MOVE "Y" TO VALID-RECORD ELSE MOVE "N" TO VALID-RECORD END-IF. FINALIZATION-SECTION SECTION. * Section for cleanup and reporting CLOSE-FILES. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE CLOSE ERROR-FILE. DISPLAY-STATISTICS. DISPLAY "Processing complete" DISPLAY "Records processed: " RECORD-COUNT DISPLAY "Errors encountered: " ERROR-COUNT.

Sections provide logical grouping and can be called with PERFORM section-name.

Paragraphs vs Sections

FeatureParagraphsSections
Definitionparagraph-name.section-name SECTION.
ContentSingle code blockMultiple paragraphs
CallingPERFORM paragraph-namePERFORM section-name
Use CaseIndividual functionsMajor program divisions
ScopeSmall, focused tasksLarge, related operations

Top-Down Design

Top-down design is a problem-solving approach that starts with the overall problem and breaks it down into smaller, manageable subproblems. This approach is fundamental to structured programming.

Design Process

Top-down design follows these steps:

  1. Define the main problem - Understand what the program needs to accomplish
  2. Break into major functions - Identify the main operations needed
  3. Refine each function - Break major functions into smaller operations
  4. Continue refinement - Keep breaking down until you reach simple operations
  5. Implement bottom-up - Code the simplest operations first, then build up

Example: Customer Processing System

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
* Level 1: Main Program PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-CUSTOMERS PERFORM FINALIZATION STOP RUN. * Level 2: Major Functions INITIALIZATION. PERFORM OPEN-FILES PERFORM INITIALIZE-COUNTERS PERFORM WRITE-REPORT-HEADER. PROCESS-CUSTOMERS. PERFORM UNTIL END-OF-FILE PERFORM READ-CUSTOMER-RECORD IF NOT END-OF-FILE PERFORM PROCESS-SINGLE-CUSTOMER END-IF END-PERFORM. FINALIZATION. PERFORM CLOSE-FILES PERFORM DISPLAY-STATISTICS. * Level 3: Detailed Operations PROCESS-SINGLE-CUSTOMER. PERFORM VALIDATE-CUSTOMER-DATA IF VALID-CUSTOMER PERFORM CALCULATE-CUSTOMER-TOTALS PERFORM WRITE-CUSTOMER-REPORT ELSE PERFORM LOG-CUSTOMER-ERROR END-IF. VALIDATE-CUSTOMER-DATA. PERFORM CHECK-CUSTOMER-ID PERFORM CHECK-CUSTOMER-NAME PERFORM CHECK-CUSTOMER-AMOUNT. CALCULATE-CUSTOMER-TOTALS. PERFORM CALCULATE-DISCOUNT PERFORM CALCULATE-TAX PERFORM CALCULATE-FINAL-AMOUNT. * Level 4: Simple Operations CHECK-CUSTOMER-ID. IF CUSTOMER-ID = SPACES OR CUSTOMER-ID = ZEROS MOVE "N" TO VALID-CUSTOMER MOVE "Invalid customer ID" TO ERROR-MESSAGE END-IF. CALCULATE-DISCOUNT. EVALUATE CUSTOMER-TYPE WHEN "PREMIUM" COMPUTE DISCOUNT = ORDER-AMOUNT * 0.15 WHEN "STANDARD" COMPUTE DISCOUNT = ORDER-AMOUNT * 0.10 WHEN OTHER MOVE 0 TO DISCOUNT END-EVALUATE.

Each level breaks down the problem into smaller, more manageable pieces.

Design Hierarchy Example

Level 1: MAIN-PROCESS
Level 2: INITIALIZATION
Level 3: OPEN-FILES
Level 3: INITIALIZE-COUNTERS
Level 3: WRITE-REPORT-HEADER
Level 2: PROCESS-CUSTOMERS
Level 3: READ-CUSTOMER-RECORD
Level 3: PROCESS-SINGLE-CUSTOMER
Level 4: VALIDATE-CUSTOMER-DATA
Level 4: CALCULATE-CUSTOMER-TOTALS
Level 4: WRITE-CUSTOMER-REPORT
Level 2: FINALIZATION
Level 3: CLOSE-FILES
Level 3: DISPLAY-STATISTICS

Error Handling in Structured Programs

Proper error handling is essential in structured programming. It ensures that programs can handle unexpected conditions gracefully and provide meaningful feedback.

Structured Error Handling

Implement error handling using structured programming principles:

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
PROCESS-CUSTOMER-RECORD. * Structured error handling PERFORM VALIDATE-CUSTOMER-DATA IF VALID-CUSTOMER PERFORM PROCESS-VALID-CUSTOMER ELSE PERFORM HANDLE-CUSTOMER-ERROR END-IF. VALIDATE-CUSTOMER-DATA. MOVE "Y" TO VALID-CUSTOMER PERFORM CHECK-CUSTOMER-ID IF VALID-CUSTOMER = "Y" PERFORM CHECK-CUSTOMER-NAME END-IF IF VALID-CUSTOMER = "Y" PERFORM CHECK-CUSTOMER-AMOUNT END-IF. CHECK-CUSTOMER-ID. IF CUSTOMER-ID = SPACES OR CUSTOMER-ID = ZEROS MOVE "N" TO VALID-CUSTOMER MOVE "Invalid customer ID" TO ERROR-MESSAGE PERFORM LOG-VALIDATION-ERROR END-IF. HANDLE-CUSTOMER-ERROR. ADD 1 TO ERROR-COUNT PERFORM LOG-CUSTOMER-ERROR PERFORM WRITE-ERROR-REPORT. LOG-VALIDATION-ERROR. MOVE CUSTOMER-ID TO ERROR-CUSTOMER-ID MOVE ERROR-MESSAGE TO ERROR-DESCRIPTION MOVE CURRENT-DATE TO ERROR-DATE MOVE CURRENT-TIME TO ERROR-TIME WRITE ERROR-RECORD FROM ERROR-LINE.

Each error condition is handled in a structured, predictable way.

File Error Handling

Handle file operation errors systematically:

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
OPEN-FILES. PERFORM OPEN-INPUT-FILE IF INPUT-FILE-STATUS = "00" PERFORM OPEN-OUTPUT-FILE IF OUTPUT-FILE-STATUS NOT = "00" PERFORM HANDLE-OUTPUT-FILE-ERROR END-IF ELSE PERFORM HANDLE-INPUT-FILE-ERROR END-IF. OPEN-INPUT-FILE. OPEN INPUT CUSTOMER-FILE MOVE CUSTOMER-FILE-STATUS TO INPUT-FILE-STATUS. OPEN-OUTPUT-FILE. OPEN OUTPUT REPORT-FILE MOVE REPORT-FILE-STATUS TO OUTPUT-FILE-STATUS. HANDLE-INPUT-FILE-ERROR. EVALUATE INPUT-FILE-STATUS WHEN "35" DISPLAY "Customer file not found" WHEN "37" DISPLAY "Insufficient permissions for customer file" WHEN OTHER DISPLAY "Input file error: " INPUT-FILE-STATUS END-EVALUATE MOVE 1 TO RETURN-CODE STOP RUN. HANDLE-OUTPUT-FILE-ERROR. EVALUATE OUTPUT-FILE-STATUS WHEN "37" DISPLAY "Insufficient permissions for report file" WHEN OTHER DISPLAY "Output file error: " OUTPUT-FILE-STATUS END-EVALUATE MOVE 2 TO RETURN-CODE STOP RUN.

File errors are handled with specific error codes and appropriate actions.

Error Recovery Strategies

  • Graceful degradation - Continue processing other records when one fails
  • Error logging - Record all errors for later analysis
  • User notification - Provide clear error messages to users
  • Retry logic - Attempt operations multiple times when appropriate
  • Cleanup procedures - Ensure resources are properly released
  • Status reporting - Report success/failure counts at completion

Best Practices and Guidelines

Following these best practices ensures that your COBOL programs are well-structured, maintainable, and reliable.

Structured Programming Best Practices

  • Avoid GOTO statements - Use structured control flow instead
  • Use meaningful names - Choose descriptive names for paragraphs, variables, and files
  • Keep paragraphs small - Each paragraph should have a single, clear purpose
  • Use consistent indentation - Make code structure visually clear
  • Add comprehensive comments - Explain complex logic and business rules
  • Implement proper error handling - Handle all possible error conditions
  • Use constants for magic numbers - Define constants for repeated values
  • Test each module independently - Verify individual components work correctly

Code Organization Guidelines

AspectGuidelineBenefit
Paragraph SizeKeep under 50 linesEasier to understand and test
Nesting DepthLimit to 3-4 levelsPrevents complex logic
Variable NamesUse descriptive namesSelf-documenting code
CommentsExplain why, not whatClarifies intent
Error HandlingHandle all exceptionsRobust programs

Performance Considerations

  • Minimize PERFORM overhead - Don't create paragraphs for single statements
  • Use efficient control structures - Choose appropriate IF vs EVALUATE
  • Optimize loop structures - Use appropriate PERFORM variations
  • Reduce file I/O - Batch operations when possible
  • Use appropriate data types - Choose efficient USAGE clauses
  • Profile performance - Measure and optimize bottlenecks

Maintenance Guidelines

  • Document changes - Keep change logs and update comments
  • Use version control - Track all code modifications
  • Review code regularly - Conduct peer reviews for quality
  • Test thoroughly - Verify changes don't break existing functionality
  • Update documentation - Keep program documentation current
  • Follow coding standards - Maintain consistency across the team

Test Your Knowledge

1. What are the three basic control structures in structured programming?

  • Sequence, Selection, and Iteration
  • Input, Process, and Output
  • Read, Write, and Compute
  • Open, Close, and Delete

2. What is the purpose of the PERFORM statement in structured COBOL programming?

  • To open files
  • To create modular, reusable code blocks
  • To define data structures
  • To handle errors

3. Which COBOL feature helps implement the selection control structure?

  • PERFORM statement
  • IF-ELSE and EVALUATE statements
  • READ statement
  • MOVE statement

4. What is the main benefit of using structured programming in COBOL?

  • Faster execution speed
  • Improved code readability and maintainability
  • Smaller program size
  • Better memory usage

5. What is a paragraph in COBOL structured programming?

  • A comment block
  • A named section of code that can be called with PERFORM
  • A data definition
  • A file description

Frequently Asked Questions