MainframeMaster

COBOL Error Handling Concepts

Error handling in COBOL involves detecting, managing, and recovering from errors that occur during program execution. Effective error handling ensures programs continue to operate reliably even when unexpected conditions arise. Understanding error handling concepts is essential for building robust, production-ready COBOL applications that can handle various error conditions gracefully.

Understanding Error Handling

Error handling in COBOL encompasses all methods of detecting, managing, and recovering from errors including file errors, data validation errors, arithmetic errors, and system errors. Proper error handling prevents program crashes, ensures data integrity, and provides meaningful error messages. Different error handling techniques are appropriate for different types of errors and program requirements.

File Error Handling

1. File Status Codes

File status codes are two-character codes that indicate the result of file operations. These codes help programs detect and respond to file-related errors and conditions such as end-of-file, file not found, or permission errors.

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
DATA DIVISION. FILE SECTION. FD INPUT-FILE. 01 INPUT-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 FILE-CONTROLS. 05 FILE-STATUS PIC XX VALUE '00'. 88 FILE-OK VALUE '00'. 88 FILE-EOF VALUE '10'. 88 FILE-ERROR VALUE '23' '24' '30' '34' '35' '37' '38' '39'. PROCEDURE DIVISION. PROCESS-FILE. OPEN INPUT INPUT-FILE IF NOT FILE-OK DISPLAY 'ERROR: Cannot open input file. Status: ' FILE-STATUS PERFORM FILE-ERROR-HANDLING STOP RUN END-IF PERFORM UNTIL FILE-EOF READ INPUT-FILE IF FILE-OK PERFORM PROCESS-RECORD ELSE IF FILE-EOF DISPLAY 'End of file reached' ELSE DISPLAY 'ERROR: File read error. Status: ' FILE-STATUS PERFORM FILE-ERROR-HANDLING END-IF END-IF END-PERFORM CLOSE INPUT-FILE

File status codes provide detailed information about file operations. Common codes include '00' for success, '10' for end-of-file, and various error codes for different failure conditions. Always check file status after file operations.

2. File Error Recovery

File error recovery involves implementing procedures to handle file errors gracefully, retry operations when appropriate, and provide fallback mechanisms for critical file 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
PROCEDURE DIVISION. FILE-ERROR-HANDLING. DISPLAY 'Handling file error with status: ' FILE-STATUS EVALUATE FILE-STATUS WHEN '23' DISPLAY 'File not found - attempting to create' PERFORM CREATE-FILE-IF-NEEDED WHEN '24' DISPLAY 'File locked - retrying in 5 seconds' PERFORM WAIT-AND-RETRY WHEN '30' DISPLAY 'Permission denied - checking access rights' PERFORM CHECK-PERMISSIONS WHEN '34' DISPLAY 'Disk full - attempting cleanup' PERFORM CLEANUP-DISK-SPACE WHEN OTHER DISPLAY 'Unrecoverable file error' PERFORM TERMINATE-GRACEFULLY END-EVALUATE. WAIT-AND-RETRY. MOVE 5 TO WAIT-SECONDS PERFORM VARYING RETRY-COUNT FROM 1 BY 1 UNTIL RETRY-COUNT > 3 DISPLAY 'Retry attempt ' RETRY-COUNT PERFORM DELAY-OPERATION PERFORM ATTEMPT-FILE-OPERATION IF FILE-OK EXIT PERFORM END-IF END-PERFORM

File error recovery provides specific handling for different error conditions. Retry mechanisms, fallback procedures, and graceful degradation help maintain program stability.

Data Validation

1. Input Validation

Input validation checks data for correctness, format compliance, and business rule adherence before processing. This prevents errors caused by invalid or malformed data.

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
PROCEDURE DIVISION. VALIDATE-INPUT-DATA. DISPLAY 'Validating input data' *> Check for numeric data IF INPUT-AMOUNT NOT NUMERIC DISPLAY 'ERROR: Amount must be numeric: ' INPUT-AMOUNT MOVE 'INVALID' TO VALIDATION-STATUS PERFORM INVALID-DATA-HANDLING END-IF *> Check range IF INPUT-AMOUNT < 0 OR INPUT-AMOUNT > 999999.99 DISPLAY 'ERROR: Amount out of range: ' INPUT-AMOUNT MOVE 'INVALID' TO VALIDATION-STATUS PERFORM INVALID-DATA-HANDLING END-IF *> Check required fields IF INPUT-NAME = SPACES DISPLAY 'ERROR: Name is required' MOVE 'INVALID' TO VALIDATION-STATUS PERFORM INVALID-DATA-HANDLING END-IF *> Check format IF INPUT-DATE NOT = FUNCTION CURRENT-DATE(1:8) DISPLAY 'ERROR: Invalid date format: ' INPUT-DATE MOVE 'INVALID' TO VALIDATION-STATUS PERFORM INVALID-DATA-HANDLING END-IF MOVE 'VALID' TO VALIDATION-STATUS DISPLAY 'Input validation passed'

Input validation ensures data integrity by checking data types, ranges, formats, and business rules. Comprehensive validation prevents processing errors and maintains data quality.

2. Business Rule Validation

Business rule validation enforces specific business logic and constraints that must be satisfied for data to be considered valid for processing.

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. VALIDATE-BUSINESS-RULES. DISPLAY 'Validating business rules' *> Check credit limit IF CUSTOMER-BALANCE + TRANSACTION-AMOUNT > CREDIT-LIMIT DISPLAY 'ERROR: Transaction exceeds credit limit' DISPLAY 'Balance: ' CUSTOMER-BALANCE DISPLAY 'Transaction: ' TRANSACTION-AMOUNT DISPLAY 'Credit Limit: ' CREDIT-LIMIT MOVE 'REJECTED' TO TRANSACTION-STATUS PERFORM BUSINESS-RULE-ERROR END-IF *> Check account status IF ACCOUNT-STATUS = 'CLOSED' DISPLAY 'ERROR: Cannot process transaction on closed account' MOVE 'REJECTED' TO TRANSACTION-STATUS PERFORM BUSINESS-RULE-ERROR END-IF *> Check transaction limits IF DAILY-TRANSACTION-COUNT >= MAX-DAILY-TRANSACTIONS DISPLAY 'ERROR: Daily transaction limit exceeded' MOVE 'REJECTED' TO TRANSACTION-STATUS PERFORM BUSINESS-RULE-ERROR END-IF MOVE 'APPROVED' TO TRANSACTION-STATUS DISPLAY 'Business rule validation passed'

Business rule validation enforces specific business constraints and logic. These rules ensure transactions comply with business policies and regulatory requirements.

Arithmetic Error Handling

1. Division by Zero

Division by zero errors occur when attempting to divide by zero. COBOL provides mechanisms to detect and handle these errors before they cause program termination.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
PROCEDURE DIVISION. SAFE-DIVISION. DISPLAY 'Performing safe division' *> Check for division by zero IF DIVISOR = 0 DISPLAY 'ERROR: Division by zero attempted' MOVE 0 TO RESULT MOVE 'ERROR' TO CALCULATION-STATUS PERFORM ARITHMETIC-ERROR-HANDLING ELSE DIVIDE DIVIDEND BY DIVISOR GIVING RESULT MOVE 'SUCCESS' TO CALCULATION-STATUS DISPLAY 'Division result: ' RESULT END-IF. ARITHMETIC-ERROR-HANDLING. DISPLAY 'Handling arithmetic error' MOVE 0 TO RESULT ADD 1 TO ERROR-COUNT DISPLAY 'Error count: ' ERROR-COUNT

Division by zero handling prevents program crashes by checking divisors before division operations. Always validate divisors and provide appropriate error handling.

2. Overflow Handling

Overflow handling manages situations where arithmetic operations produce results that exceed the capacity of the receiving field, preventing data corruption and program errors.

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. SAFE-ARITHMETIC. DISPLAY 'Performing safe arithmetic' *> Check for potential overflow COMPUTE TEMP-RESULT = FIELD-1 + FIELD-2 IF TEMP-RESULT > MAX-VALUE DISPLAY 'ERROR: Arithmetic overflow detected' DISPLAY 'Field 1: ' FIELD-1 DISPLAY 'Field 2: ' FIELD-2 DISPLAY 'Result would be: ' TEMP-RESULT DISPLAY 'Maximum allowed: ' MAX-VALUE MOVE MAX-VALUE TO RESULT MOVE 'OVERFLOW' TO CALCULATION-STATUS PERFORM OVERFLOW-HANDLING ELSE MOVE TEMP-RESULT TO RESULT MOVE 'SUCCESS' TO CALCULATION-STATUS DISPLAY 'Arithmetic result: ' RESULT END-IF. OVERFLOW-HANDLING. DISPLAY 'Handling arithmetic overflow' ADD 1 TO OVERFLOW-COUNT DISPLAY 'Overflow count: ' OVERFLOW-COUNT

Overflow handling prevents data corruption by checking results before assignment. Use temporary variables for calculations and validate results before moving to target fields.

Error Recovery Strategies

1. Graceful Degradation

Graceful degradation allows programs to continue operating with reduced functionality when errors occur, rather than terminating completely.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
PROCEDURE DIVISION. GRACEFUL-DEGRADATION. DISPLAY 'Implementing graceful degradation' *> Try primary operation PERFORM PRIMARY-OPERATION IF OPERATION-STATUS = 'FAILED' DISPLAY 'Primary operation failed, trying fallback' PERFORM FALLBACK-OPERATION IF FALLBACK-STATUS = 'FAILED' DISPLAY 'Fallback failed, using default values' PERFORM USE-DEFAULTS END-IF END-IF DISPLAY 'Operation completed with status: ' FINAL-STATUS. USE-DEFAULTS. DISPLAY 'Using default values for degraded operation' MOVE 'DEFAULT' TO OPERATION-RESULT MOVE 'DEGRADED' TO FINAL-STATUS

Graceful degradation provides fallback mechanisms when primary operations fail. This approach maintains program functionality even when some features are unavailable.

2. Error Logging and Reporting

Error logging and reporting capture error information for analysis, debugging, and system monitoring. This helps identify patterns and improve system reliability.

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
PROCEDURE DIVISION. LOG-ERROR. DISPLAY 'Logging error information' *> Capture error details MOVE FUNCTION CURRENT-DATE TO ERROR-TIMESTAMP MOVE PROGRAM-NAME TO ERROR-PROGRAM MOVE ERROR-CODE TO ERROR-NUMBER MOVE ERROR-MESSAGE TO ERROR-DESCRIPTION *> Write to error log WRITE ERROR-LOG-RECORD *> Update error statistics ADD 1 TO ERROR-COUNT ADD 1 TO DAILY-ERROR-COUNT DISPLAY 'Error logged: ' ERROR-NUMBER ' - ' ERROR-DESCRIPTION DISPLAY 'Total errors today: ' DAILY-ERROR-COUNT. REPORT-ERRORS. DISPLAY 'Generating error report' DISPLAY 'Total errors: ' ERROR-COUNT DISPLAY 'Daily errors: ' DAILY-ERROR-COUNT DISPLAY 'Last error: ' ERROR-NUMBER ' - ' ERROR-DESCRIPTION

Error logging captures detailed error information including timestamps, program names, error codes, and descriptions. This information helps with debugging and system monitoring.

Best Practices for Error Handling

Common Error Handling Patterns