MainframeMaster

COBOL Tutorial

Iteration Control in COBOL

Progress0 of 0 lessons

EXIT PERFORM Statement

The EXIT PERFORM statement provides a structured way to terminate a PERFORM loop before its normal completion condition is met. This is equivalent to the "break" statement in many modern programming languages.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
PERFORM UNTIL condition-1 statement-1 statement-2 IF condition-2 EXIT PERFORM END-IF statement-3 END-PERFORM.

When condition-2 is true, the EXIT PERFORM statement immediately terminates the loop, and control passes to the statement following END-PERFORM.

EXIT PERFORM Variants

cobol
1
2
3
4
5
6
7
8
9
10
* Basic EXIT PERFORM - ends the current loop completely IF record-not-found EXIT PERFORM END-IF. * EXIT PERFORM CYCLE - ends current iteration, continues with next * (Available in newer COBOL standards) IF skip-this-record EXIT PERFORM CYCLE END-IF.

Note that EXIT PERFORM CYCLE is similar to the "continue" statement in other languages, skipping the rest of the current iteration and moving to the next one.

Practical Example

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
IDENTIFICATION DIVISION. PROGRAM-ID. EXITPERF. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 ACCOUNT-STATUS PIC X. 88 ACCOUNT-ACTIVE VALUE 'A'. 88 ACCOUNT-INACTIVE VALUE 'I'. 88 ACCOUNT-SUSPENDED VALUE 'S'. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. OPEN INPUT CUSTOMER-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ PERFORM UNTIL END-OF-FILE EVALUATE TRUE WHEN ACCOUNT-INACTIVE DISPLAY 'Inactive account found: ' CUSTOMER-ID EXIT PERFORM WHEN ACCOUNT-SUSPENDED DISPLAY 'Processing suspended account: ' CUSTOMER-ID WHEN ACCOUNT-ACTIVE DISPLAY 'Processing active account: ' CUSTOMER-ID PERFORM PROCESS-ACTIVE-ACCOUNT END-EVALUATE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ END-PERFORM CLOSE CUSTOMER-FILE STOP RUN. PROCESS-ACTIVE-ACCOUNT. * Process active account logic here CONTINUE.

In this example, when an inactive account is found, the program exits the processing loop completely, effectively stopping any further customer record processing.

Key Points About EXIT PERFORM

  • EXIT PERFORM can only be used within an in-line PERFORM statement (with END-PERFORM)
  • It affects only the innermost PERFORM loop in which it appears
  • It provides a structured alternative to GO TO for loop termination
  • EXIT PERFORM cannot be used with out-of-line PERFORM statements (those referring to paragraphs)
  • In nested loops, multiple EXIT PERFORM statements may be needed for different scenarios

CONTINUE Statement

The CONTINUE statement is a "no operation" statement that does nothing. It serves as a placeholder in situations where the syntax requires a statement but no actual processing is needed.

CONTINUE Usage

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
* As a placeholder in an IF statement IF customer-balance > 1000 PERFORM PROCESS-HIGH-VALUE-CUSTOMER ELSE CONTINUE END-IF. * As a placeholder in a paragraph that might be empty PROCESS-SPECIAL-CASES. IF no-special-cases CONTINUE ELSE PERFORM HANDLE-SPECIAL-CASE END-IF.

CONTINUE is particularly useful in maintaining structured programming when a specific branch of logic doesn't require any action.

CONTINUE vs. NEXT SENTENCE

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
* Using CONTINUE (modern approach) IF condition-1 CONTINUE ELSE PERFORM some-paragraph END-IF. * Using NEXT SENTENCE (older approach) IF condition-1 NEXT SENTENCE ELSE PERFORM some-paragraph END-IF.

CONTINUE is preferred over the older NEXT SENTENCE, as NEXT SENTENCE transfers control to the statement following the next period, which can lead to unexpected behavior if the structure of the code changes.

Common Uses for CONTINUE

  • As an empty ELSE clause in an IF statement
  • As a placeholder in empty paragraphs that may be called
  • To improve code readability by explicitly showing where no action is taken
  • As a target for a GO TO when structured programming cannot be used
  • To satisfy compiler requirements for certain statement structures

Controlling Loop Execution

COBOL provides several mechanisms for controlling the flow of loop execution beyond basic termination conditions. These techniques allow for more sophisticated iteration control in complex business applications.

Loop Testing Options

cobol
1
2
3
4
5
6
7
8
9
* TEST BEFORE - Condition checked before each iteration (default) PERFORM WITH TEST BEFORE UNTIL counter > 10 ADD 1 TO counter END-PERFORM. * TEST AFTER - Condition checked after each iteration PERFORM WITH TEST AFTER UNTIL counter > 10 ADD 1 TO counter END-PERFORM.

TEST BEFORE ensures the loop may execute zero times if the condition is initially true. TEST AFTER ensures the loop always executes at least once, like a "do-while" loop.

Using Flags for Loop Control

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
IDENTIFICATION DIVISION. PROGRAM-ID. LOOPCTRL. DATA DIVISION. WORKING-STORAGE SECTION. 01 PROCESS-FLAG PIC X VALUE 'Y'. 88 CONTINUE-PROCESSING VALUE 'Y'. 88 STOP-PROCESSING VALUE 'N'. 01 RECORD-COUNTER PIC 9(5) VALUE ZEROS. 01 MAX-RECORDS PIC 9(5) VALUE 1000. 01 ERROR-FLAG PIC X VALUE 'N'. 88 ERROR-FOUND VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. OPEN INPUT DATA-FILE PERFORM PROCESS-RECORDS UNTIL STOP-PROCESSING OR RECORD-COUNTER >= MAX-RECORDS OR ERROR-FOUND CLOSE DATA-FILE EVALUATE TRUE WHEN RECORD-COUNTER >= MAX-RECORDS DISPLAY 'Maximum record limit reached: ' RECORD-COUNTER WHEN ERROR-FOUND DISPLAY 'Processing stopped due to error' WHEN OTHER DISPLAY 'Normal end of processing' END-EVALUATE STOP RUN. PROCESS-RECORDS. READ DATA-FILE AT END SET STOP-PROCESSING TO TRUE EXIT PARAGRAPH END-READ ADD 1 TO RECORD-COUNTER PERFORM VALIDATE-RECORD IF ERROR-FOUND EXIT PARAGRAPH END-IF PERFORM PROCESS-VALID-RECORD. VALIDATE-RECORD. * Validation logic here IF invalid-data-condition SET ERROR-FOUND TO TRUE END-IF. PROCESS-VALID-RECORD. * Processing logic here CONTINUE.

This example demonstrates using multiple flags and conditions to control loop execution, with early termination possible through several different conditions.

Loop Control with Complex Conditions

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
* Multiple exit conditions using complex logic PERFORM UNTIL (record-count >= max-records) OR (error-count > acceptable-errors) OR (processing-time > time-limit) OR end-of-file PERFORM PROCESS-RECORD IF serious-error DISPLAY 'Critical error encountered' EXIT PERFORM END-IF READ input-file AT END SET end-of-file TO TRUE END-READ END-PERFORM.

Complex conditions can be combined to create sophisticated loop control that handles various business scenarios and exceptional conditions.

Techniques for Advanced Loop Control

  • Using 88-level condition names to make loop control more readable
  • Combining multiple termination conditions with AND/OR logic
  • Implementing safety counters to prevent excessive iterations
  • Using EXIT PERFORM strategically for exceptional conditions
  • Separating loop control logic into dedicated paragraphs for better organization

Preventing Infinite Loops

Infinite loops are a common programming error that can cause system hangs, excessive resource consumption, and production outages. COBOL developers should implement safeguards to prevent and detect infinite loops.

Safety Counters

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
* Using a safety counter to prevent infinite loops 01 SAFETY-COUNTER PIC 9(6) VALUE ZERO. 01 MAX-ITERATIONS PIC 9(6) VALUE 100000. * In the procedure division: PERFORM PROCESS-DATA VARYING record-index FROM 1 BY 1 UNTIL record-index > record-count OR safety-counter > max-iterations ADD 1 TO safety-counter IF safety-counter > max-iterations DISPLAY 'WARNING: Maximum iteration count exceeded' DISPLAY 'Possible infinite loop detected' * Add error handling here END-IF END-PERFORM.

A safety counter provides a last-resort mechanism to prevent infinite loops by forcing termination after a predefined maximum number of iterations.

Common Causes of Infinite Loops

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
* Problem 1: Condition never becomes true PERFORM UNTIL WS-COUNTER = 10 ADD 1 TO WS-COUNT * Wrong variable name! END-PERFORM. * Problem 2: Condition is modified incorrectly PERFORM UNTIL WS-COUNTER >= 10 COMPUTE WS-COUNTER = WS-COUNTER - 1 * Going the wrong direction! END-PERFORM. * Problem 3: End-of-file condition never set PERFORM UNTIL EOF-FLAG = 'Y' * Read file logic here but missing EOF check PERFORM PROCESS-RECORD END-PERFORM.

Understanding common causes of infinite loops helps in preventing them during development and troubleshooting them in existing code.

Best Practices for Loop Safety

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
70
71
72
73
74
75
IDENTIFICATION DIVISION. PROGRAM-ID. LOOPSAFE. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTERS. 05 RECORD-COUNTER PIC 9(6) VALUE ZEROS. 05 SAFETY-COUNTER PIC 9(6) VALUE ZEROS. 05 MAX-ITERATIONS PIC 9(6) VALUE 999999. 01 FLAGS. 05 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 05 ERROR-FLAG PIC X VALUE 'N'. 88 ERROR-DETECTED VALUE 'Y'. 05 LOOP-STATUS PIC 9 VALUE 0. 88 NORMAL-COMPLETION VALUE 0. 88 EOF-COMPLETION VALUE 1. 88 ERROR-COMPLETION VALUE 2. 88 SAFETY-COMPLETION VALUE 3. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL END-OF-FILE OR ERROR-DETECTED OR SAFETY-COUNTER > MAX-ITERATIONS EVALUATE TRUE WHEN EOF-COMPLETION DISPLAY 'Normal completion - End of file reached' WHEN ERROR-COMPLETION DISPLAY 'Process terminated due to errors' WHEN SAFETY-COMPLETION DISPLAY 'WARNING: Safety limit reached - possible infinite loop' WHEN OTHER DISPLAY 'Unknown termination condition' END-EVALUATE PERFORM CLEANUP STOP RUN. INITIALIZATION. OPEN INPUT DATA-FILE INITIALIZE COUNTERS PERFORM READ-RECORD. PROCESS-RECORDS. PERFORM PROCESS-SINGLE-RECORD ADD 1 TO SAFETY-COUNTER IF SAFETY-COUNTER > MAX-ITERATIONS MOVE 3 TO LOOP-STATUS EXIT PARAGRAPH END-IF PERFORM READ-RECORD. READ-RECORD. READ DATA-FILE AT END SET END-OF-FILE TO TRUE MOVE 1 TO LOOP-STATUS END-READ. PROCESS-SINGLE-RECORD. ADD 1 TO RECORD-COUNTER * Process record logic here IF serious-error-condition SET ERROR-DETECTED TO TRUE MOVE 2 TO LOOP-STATUS END-IF. CLEANUP. CLOSE DATA-FILE.

This comprehensive example demonstrates a robust approach to loop safety with multiple safeguards, clear status tracking, and proper error handling.

Safeguards Against Infinite Loops

  • Always increment/modify loop control variables inside the loop
  • Verify that loop termination conditions can eventually be met
  • Implement safety counters as a backup termination mechanism
  • Use TEST BEFORE for loops that might need to execute zero times
  • Double-check file I/O operations to ensure proper EOF handling
  • For complex loop logic, document the termination conditions clearly
  • Consider using compiler options that detect potential infinite loops

Loop Performance Considerations

Loop performance is crucial in COBOL applications, especially those processing large volumes of data. Optimizing loops can significantly improve overall application performance and resource utilization.

Common Performance Bottlenecks

cobol
1
2
3
4
5
6
7
8
9
10
11
* Inefficient: Calculating the same value repeatedly in a loop PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > WS-RECORD-COUNT COMPUTE WS-RESULT = WS-FIXED-VALUE * 12 / 100 MOVE WS-RESULT TO WS-TABLE-ITEM(WS-IDX) END-PERFORM. * Better: Calculate invariant expressions once, outside the loop COMPUTE WS-RESULT = WS-FIXED-VALUE * 12 / 100 PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > WS-RECORD-COUNT MOVE WS-RESULT TO WS-TABLE-ITEM(WS-IDX) END-PERFORM.

Moving invariant calculations outside loops is a fundamental optimization technique that can significantly improve performance.

Data Types and Loop Performance

cobol
1
2
3
4
5
6
7
8
* Inefficient: Using DISPLAY numeric items for loop counters 01 LOOP-CTR PIC 9(8) VALUE ZERO. * Better: Using BINARY or COMP 01 LOOP-CTR PIC 9(8) COMP VALUE ZERO. * Better still: Using BINARY with appropriate precision 01 LOOP-CTR PIC 9(4) COMP VALUE ZERO.

Using the right data types for loop counters can improve performance, as computational numeric types (COMP) are more efficient for arithmetic operations.

I/O Optimization in Loops

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
* Inefficient: Reading a file inside a loop for each record PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 1000 OPEN INPUT REFERENCE-FILE MOVE WS-KEY-TABLE(WS-IDX) TO REF-KEY READ REFERENCE-FILE KEY IS REF-KEY INVALID KEY PERFORM HANDLE-ERROR END-READ CLOSE REFERENCE-FILE * Process record END-PERFORM. * Better: Open file once, perform all reads, then close OPEN INPUT REFERENCE-FILE PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 1000 MOVE WS-KEY-TABLE(WS-IDX) TO REF-KEY READ REFERENCE-FILE KEY IS REF-KEY INVALID KEY PERFORM HANDLE-ERROR END-READ * Process record END-PERFORM CLOSE REFERENCE-FILE. * Best: Load reference data into memory once, then process PERFORM LOAD-REFERENCE-TABLE PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 1000 * Use in-memory table instead of file I/O PERFORM FIND-IN-REFERENCE-TABLE * Process record END-PERFORM.

Minimizing I/O operations is one of the most effective ways to improve COBOL performance, as file operations are typically much slower than memory access.

Nested Loop Optimization

cobol
1
2
3
4
5
6
7
8
9
10
11
12
* Less efficient nested loops PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 1000 PERFORM VARYING WS-INNER FROM 1 BY 1 UNTIL WS-INNER > 1000 * Some processing here END-PERFORM END-PERFORM. * More efficient: Use PERFORM VARYING with multiple indexes PERFORM VARYING WS-IDX FROM 1 BY 1 UNTIL WS-IDX > 1000 AFTER WS-INNER FROM 1 BY 1 UNTIL WS-INNER > 1000 * Some processing here END-PERFORM.

Using PERFORM VARYING with multiple indices can be more efficient than nesting separate PERFORM statements, especially for simple iterations.

Performance Optimization Techniques

  • Use COMP, BINARY, or other computational formats for loop counters and indices
  • Move invariant calculations outside of loops
  • Minimize I/O operations inside loops
  • Consider loop unrolling for small critical loops
  • Use table lookups instead of repeated file accesses
  • Use PERFORM VARYING with multiple indices for nested iterations
  • Consider compiler optimization options that target loop performance
  • For DB2 applications, use array fetches and updates instead of row-by-row processing

Exercises

Exercise 1: EXIT PERFORM Implementation

Write a COBOL program that processes a customer file and stops processing when it encounters a customer with a credit limit over $10,000. Use EXIT PERFORM to terminate the loop early.

Solution Hint

Create a loop using PERFORM UNTIL that reads customer records. Inside the loop, add an IF statement that checks if the credit limit is over $10,000, and if so, executes an EXIT PERFORM statement.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
PERFORM UNTIL end-of-file READ customer-file AT END SET end-of-file TO TRUE END-READ IF NOT end-of-file IF customer-credit-limit > 10000 DISPLAY 'High credit limit found: ' customer-id DISPLAY 'Credit limit: ' customer-credit-limit EXIT PERFORM END-IF PERFORM process-customer END-IF END-PERFORM.

Exercise 2: Preventing Infinite Loops

Modify the following code to add a safety counter that will prevent an infinite loop. The loop should terminate if it exceeds 1000 iterations, and it should display an appropriate message.

cobol
1
2
3
4
PERFORM UNTIL account-balance = ZERO SUBTRACT payment-amount FROM account-balance PERFORM CALCULATE-INTEREST END-PERFORM.
Solution
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
01 SAFETY-COUNTER PIC 9(4) COMP VALUE ZERO. 01 MAX-ITERATIONS PIC 9(4) COMP VALUE 1000. * In the procedure division: INITIALIZE SAFETY-COUNTER PERFORM UNTIL account-balance = ZERO OR SAFETY-COUNTER > MAX-ITERATIONS SUBTRACT payment-amount FROM account-balance PERFORM CALCULATE-INTEREST ADD 1 TO SAFETY-COUNTER END-PERFORM IF SAFETY-COUNTER > MAX-ITERATIONS DISPLAY 'WARNING: Maximum iteration count exceeded' DISPLAY 'Current account balance: ' account-balance DISPLAY 'Possible infinite loop detected' END-IF.

Exercise 3: Performance Optimization

Optimize the following nested loop code to improve performance.

cobol
1
2
3
4
5
6
PERFORM VARYING row-idx FROM 1 BY 1 UNTIL row-idx > 100 PERFORM VARYING col-idx FROM 1 BY 1 UNTIL col-idx > 100 COMPUTE result-table(row-idx, col-idx) = (input-value * 1.05) + (row-idx * col-idx / 100) END-PERFORM END-PERFORM.
Solution
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
* Move invariant calculation outside the loop COMPUTE WS-TEMP-VALUE = input-value * 1.05 * Use binary data types for counters 01 row-idx PIC 9(4) COMP. 01 col-idx PIC 9(4) COMP. 01 WS-TEMP-VALUE PIC 9(5)V99 COMP-3. * Use AFTER clause for nested iteration PERFORM VARYING row-idx FROM 1 BY 1 UNTIL row-idx > 100 AFTER col-idx FROM 1 BY 1 UNTIL col-idx > 100 COMPUTE result-table(row-idx, col-idx) = WS-TEMP-VALUE + (row-idx * col-idx / 100) END-PERFORM.

Exercise 4: Complex Loop Control

Write a COBOL program that processes a transaction file with the following requirements:

  • Process records until end of file OR until 5 errors are encountered OR until 1000 records are processed
  • Skip records with transaction code 'X' and continue with the next record
  • For transaction code 'Z', stop processing immediately
Solution Outline
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
DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTERS. 05 RECORD-COUNTER PIC 9(4) COMP VALUE ZERO. 05 ERROR-COUNTER PIC 9(2) COMP VALUE ZERO. 01 FLAGS. 05 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. OPEN INPUT TRANSACTION-FILE PERFORM READ-TRANSACTION PERFORM PROCESS-TRANSACTIONS UNTIL END-OF-FILE OR ERROR-COUNTER >= 5 OR RECORD-COUNTER >= 1000 DISPLAY 'Records processed: ' RECORD-COUNTER DISPLAY 'Errors encountered: ' ERROR-COUNTER CLOSE TRANSACTION-FILE STOP RUN. PROCESS-TRANSACTIONS. EVALUATE TRANSACTION-CODE WHEN 'X' * Skip this record CONTINUE WHEN 'Z' DISPLAY 'Stop code encountered - terminating processing' EXIT PERFORM WHEN OTHER PERFORM PROCESS-VALID-TRANSACTION END-EVALUATE ADD 1 TO RECORD-COUNTER PERFORM READ-TRANSACTION. READ-TRANSACTION. READ TRANSACTION-FILE AT END SET END-OF-FILE TO TRUE END-READ. PROCESS-VALID-TRANSACTION. * Processing logic here IF some-error-condition ADD 1 TO ERROR-COUNTER END-IF.

Test Your Knowledge

1. What is the primary purpose of the EXIT PERFORM statement in COBOL?

  • To exit a program completely
  • To terminate the current iteration and continue with the next one
  • To prematurely exit from a PERFORM loop
  • To skip to the next paragraph

2. How does the CONTINUE statement function in COBOL?

  • It restarts the current PERFORM loop from the beginning
  • It skips to the next iteration of a loop
  • It acts as a no-operation statement that does nothing
  • It continues execution after handling an exception

3. Which of the following COBOL statements can help prevent infinite loops?

  • INITIALIZE
  • EXIT PROGRAM
  • PERFORM WITH TEST AFTER
  • PERFORM WITH TEST BEFORE

4. In a nested PERFORM structure, what happens when an EXIT PERFORM statement is encountered?

  • All loops are terminated
  • The program execution ends
  • Only the innermost loop containing the EXIT PERFORM is terminated
  • The outermost loop is terminated

5. Which is a valid performance optimization for COBOL loops?

  • Performing complex calculations inside the loop condition test
  • Moving invariant computations outside the loop
  • Using GO TO statements instead of structured PERFORM
  • Adding CONTINUE statements after each loop iteration

Frequently Asked Questions