MainframeMaster

COBOL Tutorial

Exception Handling in COBOL

Progress0 of 0 lessons

ON SIZE ERROR Clause

The ON SIZE ERROR clause is a critical exception handling feature in COBOL that catches arithmetic overflow or underflow conditions. It's used with arithmetic operations (ADD, SUBTRACT, MULTIPLY, DIVIDE, and COMPUTE) to prevent program abends when calculations exceed the defined size of result fields.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
ADD amount-1 TO amount-2 ON SIZE ERROR PERFORM size-error-handler END-ADD. MULTIPLY quantity BY price GIVING total-cost ON SIZE ERROR MOVE 999999.99 TO total-cost PERFORM log-overflow-error END-MULTIPLY. COMPUTE result = (a + b) / c ON SIZE ERROR MOVE 0 TO result MOVE "Y" TO calculation-error-flag END-COMPUTE.

Each arithmetic verb has a corresponding scope terminator (END-ADD, END-MULTIPLY, END-COMPUTE). The code in the ON SIZE ERROR block executes only when a size error occurs.

When Size Errors Occur

  • When the result of a calculation is too large for the defined receiving field
  • When division by zero is attempted
  • When numeric overflow or underflow occurs
  • When the result cannot be represented accurately in the receiving field
cobol
1
2
3
4
5
6
7
8
01 SMALL-FIELD PIC 999V99. *Max value: 999.99 01 LARGE-NUMBER PIC 9(6)V99 VALUE 123456.78. * This will cause a size error MOVE LARGE-NUMBER TO SMALL-FIELD ON SIZE ERROR DISPLAY "Error: Number too large for field" END-MOVE.

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
IDENTIFICATION DIVISION. PROGRAM-ID. SIZEERROR. DATA DIVISION. WORKING-STORAGE SECTION. 01 AMOUNTS. 05 PRINCIPAL PIC 9(5)V99 VALUE 10000.00. 05 INTEREST-RATE PIC 9V9(5) VALUE 0.0525. 05 PERIODS PIC 999 VALUE 360. 05 PAYMENT PIC 9(5)V99 VALUE ZEROS. 01 ERROR-FLAGS. 05 CALC-ERROR-FLAG PIC X VALUE 'N'. 88 CALCULATION-ERROR VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM CALCULATE-PAYMENT IF CALCULATION-ERROR DISPLAY "Error in payment calculation." DISPLAY "Please check input values." ELSE DISPLAY "Monthly payment: $" PAYMENT END-IF STOP RUN. CALCULATE-PAYMENT. * Mortgage payment formula: P = (r*PV) / (1 - (1+r)^-n) * Simplified for example COMPUTE PAYMENT ROUNDED = (INTEREST-RATE / 12 * PRINCIPAL) / (1 - (1 + INTEREST-RATE / 12) ** (- PERIODS)) ON SIZE ERROR MOVE 'Y' TO CALC-ERROR-FLAG MOVE ZEROS TO PAYMENT END-COMPUTE.

This example calculates a mortgage payment using a complex formula. The ON SIZE ERROR handler catches any arithmetic overflow and sets a flag to indicate the error.

Best Practices for ON SIZE ERROR

  • Always include ON SIZE ERROR for financial and critical calculations
  • Set specific error flags to track the type and location of errors
  • Provide meaningful default values when size errors occur
  • Log detailed information about the error for troubleshooting
  • Consider program design to minimize the possibility of size errors
  • Use appropriate field sizes with sufficient capacity for expected results

ON EXCEPTION Clause

The ON EXCEPTION clause provides error handling for various COBOL statements beyond arithmetic operations. It's commonly used with CALL, STRING, UNSTRING, XML, JSON, and other operations to catch runtime exceptions that might otherwise cause program failures.

Basic Syntax with CALL Statement

cobol
1
2
3
4
5
6
7
8
9
10
11
12
CALL "SUBPROGRAM" USING parameter-1, parameter-2 ON EXCEPTION PERFORM subprogram-not-found-handler END-CALL. CALL program-name USING customer-record ON EXCEPTION DISPLAY "Program " program-name " not found" MOVE "Y" TO program-error-flag NOT ON EXCEPTION MOVE "N" TO program-error-flag END-CALL.

The ON EXCEPTION phrase catches errors when the called program cannot be found or executed. The optional NOT ON EXCEPTION phrase executes when the call is successful.

Using ON EXCEPTION with STRING

cobol
1
2
3
4
5
6
7
8
9
10
11
12
01 RESULT-FIELD PIC X(10). 01 FIRST-NAME PIC X(15) VALUE "John". 01 LAST-NAME PIC X(20) VALUE "Smith". STRING FIRST-NAME DELIMITED BY SPACE " " DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO RESULT-FIELD ON OVERFLOW DISPLAY "Name too long for result field" MOVE FIRST-NAME TO RESULT-FIELD END-STRING.

With STRING operations, the ON OVERFLOW phrase (which is analogous to ON EXCEPTION) catches situations where the result field is too small for the concatenated data.

Comprehensive 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
46
47
48
49
50
51
52
53
54
55
56
57
58
IDENTIFICATION DIVISION. PROGRAM-ID. EXCEPTIONDEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 PROGRAM-VARIABLES. 05 SUBPROGRAM-NAME PIC X(8) VALUE "CUSTSRCH". 05 OPERATION-STATUS PIC 9. 88 OPERATION-SUCCESSFUL VALUE 0. 88 PROGRAM-NOT-FOUND VALUE 1. 88 STRING-OVERFLOW VALUE 2. 88 XML-PARSE-ERROR VALUE 3. 01 CUSTOMER-DATA. 05 CUSTOMER-ID PIC 9(5). 05 FULL-NAME PIC X(20). 05 FIRST-NAME PIC X(10). 05 LAST-NAME PIC X(15). 01 XML-DOCUMENT PIC X(500). 01 XML-STATUS PIC 9(4) BINARY. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM CALL-CUSTOMER-SEARCH PERFORM FORMAT-CUSTOMER-NAME EVALUATE TRUE WHEN OPERATION-SUCCESSFUL DISPLAY "Processing completed successfully" WHEN PROGRAM-NOT-FOUND DISPLAY "Error: Required module not available" WHEN STRING-OVERFLOW DISPLAY "Error: Name formatting failed - buffer overflow" WHEN XML-PARSE-ERROR DISPLAY "Error: XML processing failed" WHEN OTHER DISPLAY "Unknown error occurred" END-EVALUATE STOP RUN. CALL-CUSTOMER-SEARCH. CALL SUBPROGRAM-NAME USING CUSTOMER-ID, FIRST-NAME, LAST-NAME ON EXCEPTION MOVE 1 TO OPERATION-STATUS NOT ON EXCEPTION MOVE 0 TO OPERATION-STATUS END-CALL. FORMAT-CUSTOMER-NAME. STRING FIRST-NAME DELIMITED BY SPACE " " DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO FULL-NAME ON OVERFLOW MOVE 2 TO OPERATION-STATUS NOT ON OVERFLOW MOVE 0 TO OPERATION-STATUS END-STRING.

This example demonstrates using ON EXCEPTION with a CALL statement and ON OVERFLOW with a STRING operation. It uses a consistent error code approach for tracking different types of exceptions.

Common Uses of ON EXCEPTION

  • Handling missing or invalid subprograms in CALL statements
  • Catching buffer overflow in STRING and UNSTRING operations
  • Managing errors in XML PARSE and XML GENERATE statements
  • Handling errors in JSON PARSE and JSON GENERATE statements
  • Dealing with exceptions in external interface operations
  • Providing graceful degradation when services are unavailable

NOT ON SIZE ERROR

The NOT ON SIZE ERROR clause provides a way to execute specific code when an arithmetic operation completes successfully without a size error. This complementary clause to ON SIZE ERROR enables more comprehensive error handling by explicitly handling both error and success paths.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
ADD values-1 TO amounts ON SIZE ERROR PERFORM error-handling-routine NOT ON SIZE ERROR PERFORM success-routine END-ADD. COMPUTE result = complex-formula ON SIZE ERROR MOVE "Error" TO calculation-status MOVE 0 TO result NOT ON SIZE ERROR MOVE "Success" TO calculation-status PERFORM log-calculation-result END-COMPUTE.

The NOT ON SIZE ERROR block executes only when the operation completes without a size error. If ON SIZE ERROR executes, the NOT ON SIZE ERROR block is skipped.

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
46
47
IDENTIFICATION DIVISION. PROGRAM-ID. NOTSIZEERR. DATA DIVISION. WORKING-STORAGE SECTION. 01 FINANCIAL-DATA. 05 INVOICE-TOTAL PIC 9(6)V99 VALUE 123456.78. 05 DISCOUNT-RATE PIC V999 VALUE .150. 05 DISCOUNT-AMOUNT PIC 9(5)V99. 05 NET-AMOUNT PIC 9(6)V99. 01 PROCESSING-STATUS. 05 CALC-STATUS PIC X(8) VALUE SPACES. 05 ERROR-COUNT PIC 9(2) VALUE ZEROS. 05 SUCCESS-COUNT PIC 9(2) VALUE ZEROS. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM PROCESS-DISCOUNT DISPLAY "Calculation status: " CALC-STATUS DISPLAY "Invoice total: " INVOICE-TOTAL DISPLAY "Discount amount: " DISCOUNT-AMOUNT DISPLAY "Net amount: " NET-AMOUNT DISPLAY "Error count: " ERROR-COUNT DISPLAY "Success count: " SUCCESS-COUNT STOP RUN. PROCESS-DISCOUNT. * Calculate discount amount COMPUTE DISCOUNT-AMOUNT ROUNDED = INVOICE-TOTAL * DISCOUNT-RATE ON SIZE ERROR MOVE "ERROR" TO CALC-STATUS MOVE 0 TO DISCOUNT-AMOUNT ADD 1 TO ERROR-COUNT NOT ON SIZE ERROR MOVE "SUCCESS" TO CALC-STATUS ADD 1 TO SUCCESS-COUNT END-COMPUTE * Calculate net amount (invoice total - discount) COMPUTE NET-AMOUNT = INVOICE-TOTAL - DISCOUNT-AMOUNT ON SIZE ERROR MOVE "ERROR" TO CALC-STATUS MOVE INVOICE-TOTAL TO NET-AMOUNT ADD 1 TO ERROR-COUNT NOT ON SIZE ERROR ADD 1 TO SUCCESS-COUNT END-COMPUTE.

This example calculates discount and net amounts for an invoice. It uses both ON SIZE ERROR and NOT ON SIZE ERROR to track success and error counts for each calculation.

Benefits of NOT ON SIZE ERROR

  • Provides explicit handling for both success and failure paths
  • Makes the code more readable by clearly indicating expected behavior
  • Enables tracking of successful operations for auditing or statistics
  • Allows for conditional processing based on calculation success
  • Provides a structured approach to comprehensive error handling
  • Makes debugging easier by clearly separating normal and exception flows

AT END Conditions

The AT END phrase is a crucial exception handling mechanism for file operations in COBOL. It detects when a READ operation has reached the end of a file, allowing programs to handle this condition gracefully instead of abending with a file error.

Basic Syntax for Sequential Files

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
READ input-file AT END SET end-of-file TO TRUE NOT AT END PERFORM process-record END-READ. READ customer-file NEXT RECORD AT END MOVE "Y" TO EOF-FLAG DISPLAY "End of customer file reached" NOT AT END ADD 1 TO RECORD-COUNT PERFORM PROCESS-CUSTOMER END-READ.

The AT END phrase executes when no more records exist in the file. The optional NOT AT END phrase executes when a record is successfully read.

Related Conditions for Indexed Files

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
READ indexed-file KEY IS record-key INVALID KEY PERFORM record-not-found-routine NOT INVALID KEY PERFORM process-record END-READ. START indexed-file KEY >= index-key INVALID KEY DISPLAY "No records match the criteria" MOVE "Y" TO no-match-flag NOT INVALID KEY PERFORM retrieve-matching-records END-START.

For indexed files, INVALID KEY and NOT INVALID KEY serve a similar purpose to AT END and NOT AT END for sequential files. They handle cases where a record with the specified key cannot be found.

Comprehensive File Processing 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
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
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
IDENTIFICATION DIVISION. PROGRAM-ID. ATENDEXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMERS.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-FILE-STATUS. SELECT REPORT-FILE ASSIGN TO "REPORT.TXT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS REPORT-FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 ACCOUNT-BALANCE PIC S9(7)V99. FD REPORT-FILE. 01 REPORT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUS-CODES. 05 CUSTOMER-FILE-STATUS PIC XX. 88 CUSTOMER-FILE-OK VALUE "00". 88 CUSTOMER-FILE-EOF VALUE "10". 05 REPORT-FILE-STATUS PIC XX. 88 REPORT-FILE-OK VALUE "00". 01 PROGRAM-FLAGS. 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 05 ERROR-FLAG PIC X VALUE "N". 88 ERROR-OCCURRED VALUE "Y". 01 COUNTERS. 05 RECORDS-READ PIC 9(5) VALUE ZEROS. 05 RECORDS-WRITTEN PIC 9(5) VALUE ZEROS. 05 ERROR-COUNT PIC 9(3) VALUE ZEROS. 01 REPORT-FIELDS. 05 REPORT-LINE PIC X(80) VALUE SPACES. 05 REPORT-HEADER PIC X(50) VALUE "Customer Account Balance Report". 05 REPORT-FOOTER PIC X(50) VALUE SPACES. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF NOT ERROR-OCCURRED PERFORM PROCESS-RECORDS UNTIL END-OF-FILE PERFORM WRITE-FOOTER END-IF PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE IF NOT CUSTOMER-FILE-OK DISPLAY "Error opening customer file: " CUSTOMER-FILE-STATUS SET ERROR-OCCURRED TO TRUE END-IF IF NOT ERROR-OCCURRED OPEN OUTPUT REPORT-FILE IF NOT REPORT-FILE-OK DISPLAY "Error opening report file: " REPORT-FILE-STATUS SET ERROR-OCCURRED TO TRUE END-IF END-IF IF NOT ERROR-OCCURRED MOVE REPORT-HEADER TO REPORT-RECORD WRITE REPORT-RECORD INVALID KEY DISPLAY "Error writing report header" SET ERROR-OCCURRED TO TRUE NOT INVALID KEY ADD 1 TO RECORDS-WRITTEN END-WRITE END-IF. PROCESS-RECORDS. READ CUSTOMER-FILE INTO CUSTOMER-RECORD AT END SET END-OF-FILE TO TRUE NOT AT END ADD 1 TO RECORDS-READ PERFORM PROCESS-CUSTOMER-RECORD END-READ. PROCESS-CUSTOMER-RECORD. MOVE SPACES TO REPORT-LINE STRING CUSTOMER-ID DELIMITED BY SIZE ": " DELIMITED BY SIZE CUSTOMER-NAME DELIMITED BY SPACE " - Balance: " DELIMITED BY SIZE ACCOUNT-BALANCE DELIMITED BY SIZE INTO REPORT-LINE END-STRING MOVE REPORT-LINE TO REPORT-RECORD WRITE REPORT-RECORD INVALID KEY DISPLAY "Error writing record for customer: " CUSTOMER-ID ADD 1 TO ERROR-COUNT END-WRITE. WRITE-FOOTER. MOVE SPACES TO REPORT-FOOTER STRING "Total records processed: " DELIMITED BY SIZE RECORDS-READ DELIMITED BY SIZE " - Report generated: " DELIMITED BY SIZE FUNCTION CURRENT-DATE DELIMITED BY SIZE INTO REPORT-FOOTER END-STRING MOVE REPORT-FOOTER TO REPORT-RECORD WRITE REPORT-RECORD INVALID KEY DISPLAY "Error writing report footer" END-WRITE. TERMINATION. CLOSE CUSTOMER-FILE CLOSE REPORT-FILE DISPLAY "Processing complete" DISPLAY "Records read: " RECORDS-READ DISPLAY "Records written: " RECORDS-WRITTEN DISPLAY "Errors: " ERROR-COUNT.

This comprehensive example demonstrates file processing with AT END and NOT AT END clauses. It also shows proper file status checking and error handling throughout the program.

Other END Conditions in COBOL

  • SEARCH... AT END - When no matching item is found in a table search
  • RETURN... AT END - When a sort or merge file has no more records
  • STRING... ON OVERFLOW - When the receiving field is too small
  • UNSTRING... ON OVERFLOW - When all receiving fields are filled
  • INSPECT... TALLYING/REPLACING - Implied end handling when processed

Structured Error Handling Techniques

Structured error handling in COBOL involves using organized, consistent approaches to detect, report, and recover from errors. Unlike some modern languages with try-catch blocks, COBOL requires explicit error handling strategies throughout the program.

Centralized Error Handling

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
IDENTIFICATION DIVISION. PROGRAM-ID. STRUCTERR. DATA DIVISION. WORKING-STORAGE SECTION. 01 ERROR-TRACKING. 05 ERROR-STATUS PIC 9(2) VALUE ZEROS. 88 NO-ERROR VALUE 0. 88 FILE-ERROR VALUES 1 THRU 10. 88 DATA-ERROR VALUES 11 THRU 20. 88 CALCULATION-ERROR VALUES 21 THRU 30. 88 BUSINESS-RULE-ERROR VALUES 31 THRU 40. 05 ERROR-MESSAGE PIC X(80) VALUE SPACES. 05 ERROR-LOCATION PIC X(30) VALUE SPACES. 05 ERROR-SEVERITY PIC 9 VALUE 0. 88 WARNING VALUE 1. 88 ERROR VALUE 2. 88 CRITICAL VALUE 3. 88 TERMINAL VALUE 4. * Additional working storage entries... PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF NO-ERROR PERFORM PROCESS-DATA END-IF IF NOT NO-ERROR PERFORM ERROR-HANDLER END-IF PERFORM TERMINATION STOP RUN. * Other paragraphs... * Centralized error handling routine ERROR-HANDLER. DISPLAY "ERROR DETECTED" DISPLAY "Location: " ERROR-LOCATION DISPLAY "Code: " ERROR-STATUS DISPLAY "Message: " ERROR-MESSAGE EVALUATE ERROR-SEVERITY WHEN 1 DISPLAY "Warning - Processing continues" WHEN 2 DISPLAY "Error - Some functions may be limited" WHEN 3 DISPLAY "Critical error - Results may be incomplete" WHEN 4 DISPLAY "Terminal error - Processing aborted" PERFORM EMERGENCY-SHUTDOWN END-EVALUATE * Log error details to error file PERFORM LOG-ERROR-RECORD. * Specific error setting routines SET-FILE-ERROR. MOVE 1 TO ERROR-STATUS MOVE "FILE-OPEN-ERROR" TO ERROR-LOCATION MOVE "Cannot open required file" TO ERROR-MESSAGE MOVE 3 TO ERROR-SEVERITY. SET-CALCULATION-ERROR. MOVE 21 TO ERROR-STATUS MOVE "PAYMENT-CALCULATION" TO ERROR-LOCATION MOVE "Overflow in payment calculation" TO ERROR-MESSAGE MOVE 2 TO ERROR-SEVERITY.

This approach uses a centralized error handler with standardized error codes, messages, and severity levels. The program checks for errors after critical operations and routes all error handling through a common routine.

Status Code Propagation

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
* Main program calls SUB-A, which calls SUB-B * Error status propagates back up the call chain CALL "SUB-A" USING PARM-1, PARM-2, RETURN-CODE ON EXCEPTION MOVE 99 TO RETURN-CODE END-CALL IF RETURN-CODE NOT = 0 DISPLAY "Error in processing, code: " RETURN-CODE PERFORM ERROR-HANDLER END-IF * In SUB-A: CALL "SUB-B" USING SUB-PARM-1, SUB-PARM-2, SUB-RETURN-CODE ON EXCEPTION MOVE 50 TO RETURN-CODE EXIT PROGRAM END-CALL IF SUB-RETURN-CODE NOT = 0 MOVE SUB-RETURN-CODE TO RETURN-CODE EXIT PROGRAM END-IF * Continue with normal processing... * In SUB-B: COMPUTE RESULT = COMPLEX-CALCULATION ON SIZE ERROR MOVE 25 TO RETURN-CODE EXIT PROGRAM END-COMPUTE

This pattern propagates error codes back up the call chain, allowing errors detected in lower-level modules to be handled at higher levels. Each module can add context to the error information as it propagates.

Comprehensive Error Logging

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
IDENTIFICATION DIVISION. PROGRAM-ID. ERRORLOG. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ERROR-LOG-FILE ASSIGN TO "ERRORLOG.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS ERROR-LOG-STATUS. DATA DIVISION. FILE SECTION. FD ERROR-LOG-FILE. 01 ERROR-LOG-RECORD PIC X(200). WORKING-STORAGE SECTION. 01 ERROR-LOG-STATUS PIC XX. 01 ERROR-DETAILS. 05 ERROR-TIMESTAMP PIC X(26). 05 PROGRAM-ID PIC X(8) VALUE "ERRORLOG". 05 USER-ID PIC X(8). 05 TERMINAL-ID PIC X(8). 05 ERROR-CODE PIC 9(4). 05 ERROR-MODULE PIC X(20). 05 ERROR-DESCRIPTION PIC X(80). 05 ERROR-DATA PIC X(50). PROCEDURE DIVISION. * Within the program when an error is detected: LOG-ARITHMETIC-ERROR. MOVE FUNCTION CURRENT-DATE TO ERROR-TIMESTAMP ACCEPT USER-ID FROM ENVIRONMENT "USER" ACCEPT TERMINAL-ID FROM ENVIRONMENT "TERMINAL" MOVE 2157 TO ERROR-CODE MOVE "CALC-MONTHLY-PAYMENT" TO ERROR-MODULE MOVE "Size error in payment calculation" TO ERROR-DESCRIPTION MOVE PRINCIPAL-AMOUNT TO ERROR-DATA PERFORM WRITE-ERROR-LOG. WRITE-ERROR-LOG. OPEN EXTEND ERROR-LOG-FILE IF ERROR-LOG-STATUS = "00" MOVE SPACES TO ERROR-LOG-RECORD STRING ERROR-TIMESTAMP DELIMITED BY SIZE "," DELIMITED BY SIZE PROGRAM-ID DELIMITED BY SIZE "," DELIMITED BY SIZE USER-ID DELIMITED BY SIZE "," DELIMITED BY SIZE TERMINAL-ID DELIMITED BY SIZE "," DELIMITED BY SIZE ERROR-CODE DELIMITED BY SIZE "," DELIMITED BY SIZE ERROR-MODULE DELIMITED BY SPACE "," DELIMITED BY SIZE ERROR-DESCRIPTION DELIMITED BY SIZE "," DELIMITED BY SIZE ERROR-DATA DELIMITED BY SIZE INTO ERROR-LOG-RECORD END-STRING WRITE ERROR-LOG-RECORD CLOSE ERROR-LOG-FILE END-IF.

A robust logging system captures detailed information about each error, including context data that helps with troubleshooting. This example creates CSV-format log entries with timestamps, user information, error codes, and relevant data.

Principles of Structured Error Handling

  • Standardize error codes and messages across the application
  • Implement a severity system to distinguish minor warnings from critical errors
  • Check for errors immediately after operations that might fail
  • Create reusable error handling routines for common error types
  • Log detailed error information for post-mortem analysis
  • Provide meaningful error messages for end-users
  • Use defensive programming to check conditions before they cause errors
  • Implement clean termination procedures for serious errors
  • Consider recoverability for each error type

Exercises

Exercise 1: ON SIZE ERROR Implementation

Write a COBOL program that calculates compound interest using the formula A = P(1 + r/n)^(nt), where P is principal, r is interest rate, n is number of times compounded per year, and t is time in years. Implement ON SIZE ERROR handling for the calculation.

Solution Hint

Use the COMPUTE statement with the exponentiation operator (**) and include ON SIZE ERROR handling in case of overflow.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
01 INVESTMENT-DATA. 05 PRINCIPAL PIC 9(6)V99 VALUE 10000.00. 05 ANNUAL-RATE PIC 9V9(5) VALUE 0.05. 05 COMPOUNDS-PER-YEAR PIC 99 VALUE 12. 05 YEARS PIC 99 VALUE 30. 05 FINAL-AMOUNT PIC 9(7)V99. 01 CALC-ERROR-FLAG PIC X VALUE 'N'. * Compound interest calculation COMPUTE FINAL-AMOUNT ROUNDED = PRINCIPAL * (1 + ANNUAL-RATE / COMPOUNDS-PER-YEAR) ** (COMPOUNDS-PER-YEAR * YEARS) ON SIZE ERROR MOVE 'Y' TO CALC-ERROR-FLAG DISPLAY "Error: Result too large for field" NOT ON SIZE ERROR DISPLAY "Final amount after " YEARS " years: $" FINAL-AMOUNT END-COMPUTE.

Exercise 2: File Processing with AT END

Write a program that reads a customer file and creates a report of customers with balances over $1,000. Use AT END and NOT AT END to properly handle the end-of-file condition. Include error handling for file operations.

Solution Hint

Use proper file handling with AT END clauses and check file status after operations.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
* File handling with AT END example OPEN INPUT CUSTOMER-FILE IF CUSTOMER-FILE-STATUS = "00" PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE NOT AT END IF CUSTOMER-BALANCE > 1000 PERFORM WRITE-TO-REPORT END-IF END-READ END-PERFORM CLOSE CUSTOMER-FILE ELSE DISPLAY "Error opening file: " CUSTOMER-FILE-STATUS END-IF.

Exercise 3: Structured Error Handling

Design a COBOL program with a centralized error handling module. Include routines for arithmetic errors, file errors, and data validation errors. Use condition names (88-level) to track error types and severities.

Solution Hint

Create a dedicated error tracking section in WORKING-STORAGE with error codes, messages, and severity levels.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
01 ERROR-CONTROL. 05 ERROR-CODE PIC 9(4) VALUE ZEROS. 88 NO-ERROR VALUE 0. 88 FILE-ERROR VALUES 1000 THRU 1999. 88 ARITHMETIC-ERROR VALUES 2000 THRU 2999. 88 DATA-ERROR VALUES 3000 THRU 3999. 05 ERROR-SEVERITY PIC 9 VALUE 0. 88 WARNING VALUE 1. 88 ERROR VALUE 2. 88 CRITICAL VALUE 3. 05 ERROR-MESSAGE PIC X(80) VALUE SPACES. * In the main procedure, use: IF FILE-ERROR PERFORM FILE-ERROR-HANDLER ELSE IF ARITHMETIC-ERROR PERFORM ARITHMETIC-ERROR-HANDLER END-IF.

Frequently Asked Questions