MainframeMaster

COBOL Tutorial

COBOL Error Handling

Progress0 of 0 lessons

Introduction to Error Handling

Error handling is a critical aspect of COBOL programming that ensures programs operate reliably and gracefully handle unexpected situations. Proper error handling prevents program crashes, provides meaningful feedback, and enables recovery from error conditions.

Why Error Handling Matters

Effective error handling provides several benefits:

  • Program Reliability - Prevents unexpected program termination
  • Data Integrity - Ensures data remains consistent during errors
  • User Experience - Provides meaningful error messages and recovery options
  • Debugging - Helps identify and resolve issues quickly
  • Maintenance - Makes programs easier to maintain and modify
  • Audit Trail - Creates logs for tracking and analysis

Types of Errors in COBOL

COBOL programs can encounter various types of errors:

Error TypeDescriptionExamples
File Operation ErrorsErrors related to file I/O operationsFile not found, access denied, record not found
Data Validation ErrorsInvalid or unexpected data valuesInvalid input, overflow conditions, format errors
Arithmetic ErrorsMathematical operation failuresDivision by zero, overflow, underflow
Logic ErrorsProgram flow and logic problemsInfinite loops, incorrect calculations, wrong paths
System ErrorsOperating system and resource issuesMemory issues, resource conflicts, timeouts

File Status Codes

File status codes are two-character codes that provide detailed information about the result of file operations. They are essential for understanding what happened during file I/O operations and implementing appropriate error handling.

Understanding File Status Codes

File status codes are returned after file operations and indicate:

  • Success - Operation completed successfully
  • Normal Conditions - Expected conditions like end-of-file
  • Error Conditions - Problems that need to be handled
  • System Issues - Operating system or hardware problems

Each code has a specific meaning and requires appropriate handling.

Common File Status Codes

Status CodeMeaningAction Required
"00"Successful operationContinue processing
"02"Duplicate key (write operations)Handle duplicate key
"04"Record length errorCheck record format
"10"End of fileNormal end condition
"22"Duplicate key (indexed files)Handle duplicate key
"23"Record not foundHandle missing record
"30"Permanent errorCheck file/system
"35"File not foundCheck file existence
"37"File not openOpen file first
"39"File conflictCheck file access

File Status Code 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
* Example of checking file status codes IDENTIFICATION DIVISION. PROGRAM-ID. FILESTAT. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUSTOMER-ID FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-BALANCE PIC 9(7)V99. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 SEARCH-ID PIC 9(5). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM SEARCH-CUSTOMER PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE EVALUATE CUSTOMER-STATUS WHEN "00" DISPLAY "File opened successfully" WHEN "35" DISPLAY "ERROR: File not found" STOP RUN WHEN "37" DISPLAY "ERROR: File not open" STOP RUN WHEN OTHER DISPLAY "ERROR: File open failed - Status: " CUSTOMER-STATUS STOP RUN END-EVALUATE. SEARCH-CUSTOMER. DISPLAY "Enter customer ID to search: " ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY PERFORM HANDLE-INVALID-KEY NOT INVALID KEY PERFORM HANDLE-SUCCESSFUL-READ END-READ. HANDLE-INVALID-KEY. EVALUATE CUSTOMER-STATUS WHEN "23" DISPLAY "Customer " SEARCH-ID " not found" WHEN "30" DISPLAY "ERROR: Permanent file error" WHEN OTHER DISPLAY "ERROR: Read failed - Status: " CUSTOMER-STATUS END-EVALUATE. HANDLE-SUCCESSFUL-READ. IF CUSTOMER-STATUS = "00" DISPLAY "Customer found:" DISPLAY " ID: " CUSTOMER-ID DISPLAY " Name: " CUSTOMER-NAME DISPLAY " Address: " CUSTOMER-ADDRESS DISPLAY " Balance: " CUSTOMER-BALANCE ELSE DISPLAY "WARNING: Unexpected status - " CUSTOMER-STATUS END-IF. FINALIZATION. CLOSE CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "WARNING: File close error - Status: " CUSTOMER-STATUS END-IF.

This example shows comprehensive file status code checking at each step of file operations.

Error Handling Clauses

COBOL provides specific clauses for handling different types of error conditions. These clauses allow you to specify what action to take when certain conditions occur.

AT END Clause

The AT END clause is used with sequential file operations to handle the end-of-file condition when reading files.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
* AT END clause example READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG DISPLAY "End of file reached" NOT AT END PERFORM PROCESS-CUSTOMER END-READ. * Alternative AT END usage READ TRANSACTION-FILE AT END PERFORM END-OF-FILE-PROCESSING NOT AT END IF TRANSACTION-STATUS = "00" PERFORM PROCESS-TRANSACTION ELSE PERFORM HANDLE-READ-ERROR END-IF END-READ.

AT END is triggered when there are no more records to read from the file.

INVALID KEY Clause

The INVALID KEY clause is used with indexed and relative files for random access operations when key-related errors occur.

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
* INVALID KEY clause example MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY PERFORM HANDLE-INVALID-KEY NOT INVALID KEY PERFORM PROCESS-CUSTOMER END-READ. * INVALID KEY with status checking MOVE NEW-CUSTOMER-ID TO CUSTOMER-ID WRITE CUSTOMER-RECORD INVALID KEY EVALUATE CUSTOMER-STATUS WHEN "22" DISPLAY "Duplicate customer ID: " NEW-CUSTOMER-ID WHEN "23" DISPLAY "Record not found" WHEN OTHER DISPLAY "Write error - Status: " CUSTOMER-STATUS END-EVALUATE NOT INVALID KEY DISPLAY "Customer record written successfully" END-WRITE.

INVALID KEY is triggered when a record with the specified key cannot be found or when there are duplicate key violations.

ON OVERFLOW Clause

The ON OVERFLOW clause is used with STRING operations to handle overflow conditions when the target field is too small.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
* ON OVERFLOW clause example STRING FIRST-NAME DELIMITED BY SPACE, " " DELIMITED BY SIZE, LAST-NAME DELIMITED BY SIZE INTO FULL-NAME ON OVERFLOW PERFORM HANDLE-OVERFLOW NOT ON OVERFLOW DISPLAY "Name concatenated successfully" END-STRING. * ON OVERFLOW with error logging STRING FIELD1 DELIMITED BY SIZE, FIELD2 DELIMITED BY SIZE, FIELD3 DELIMITED BY SIZE INTO TARGET-FIELD ON OVERFLOW MOVE "Y" TO OVERFLOW-FLAG DISPLAY "WARNING: String overflow occurred" DISPLAY "Target field size: " LENGTH OF TARGET-FIELD NOT ON OVERFLOW MOVE "N" TO OVERFLOW-FLAG END-STRING.

ON OVERFLOW is triggered when a STRING operation would exceed the size of the target field.

ON SIZE ERROR Clause

The ON SIZE ERROR clause is used with arithmetic operations to handle overflow and underflow conditions.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
* ON SIZE ERROR clause example COMPUTE RESULT = AMOUNT1 + AMOUNT2 ON SIZE ERROR PERFORM HANDLE-ARITHMETIC-ERROR NOT ON SIZE ERROR PERFORM PROCESS-RESULT END-COMPUTE. * Division with ON SIZE ERROR COMPUTE QUOTIENT = DIVIDEND / DIVISOR ON SIZE ERROR IF DIVISOR = ZERO DISPLAY "ERROR: Division by zero" ELSE DISPLAY "ERROR: Arithmetic overflow" END-IF MOVE ZERO TO QUOTIENT NOT ON SIZE ERROR DISPLAY "Division result: " QUOTIENT END-COMPUTE.

ON SIZE ERROR is triggered when arithmetic operations result in overflow or underflow conditions.

Structured Error Handling

Structured error handling uses COBOL statements like EVALUATE to systematically check for different error conditions and handle them appropriately.

Using EVALUATE for 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
* Comprehensive error handling with EVALUATE IDENTIFICATION DIVISION. PROGRAM-ID. ERRORHANDLE. WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. 01 ERROR-COUNT PIC 9(3) VALUE ZERO. 01 SUCCESS-COUNT PIC 9(3) VALUE ZERO. 01 OPERATION-TYPE PIC X(10). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM FILE-OPERATION PERFORM DISPLAY-STATISTICS STOP RUN. FILE-OPERATION. MOVE "OPEN" TO OPERATION-TYPE OPEN INPUT CUSTOMER-FILE PERFORM CHECK-STATUS MOVE "READ" TO OPERATION-TYPE READ CUSTOMER-FILE AT END DISPLAY "End of file reached" NOT AT END PERFORM CHECK-STATUS END-READ MOVE "CLOSE" TO OPERATION-TYPE CLOSE CUSTOMER-FILE PERFORM CHECK-STATUS. CHECK-STATUS. EVALUATE FILE-STATUS WHEN "00" ADD 1 TO SUCCESS-COUNT DISPLAY OPERATION-TYPE " operation successful" WHEN "10" DISPLAY "End of file (normal condition)" WHEN "23" ADD 1 TO ERROR-COUNT DISPLAY "ERROR: Record not found" WHEN "35" ADD 1 TO ERROR-COUNT DISPLAY "ERROR: File not found" WHEN "37" ADD 1 TO ERROR-COUNT DISPLAY "ERROR: File not open" WHEN "39" ADD 1 TO ERROR-COUNT DISPLAY "ERROR: File access conflict" WHEN "30" ADD 1 TO ERROR-COUNT DISPLAY "ERROR: Permanent file error" WHEN OTHER ADD 1 TO ERROR-COUNT DISPLAY "ERROR: Unknown status " FILE-STATUS END-EVALUATE. DISPLAY-STATISTICS. DISPLAY "Operation Statistics:" DISPLAY " Successful operations: " SUCCESS-COUNT DISPLAY " Errors encountered: " ERROR-COUNT.

This example shows how to use EVALUATE for systematic error handling and statistics tracking.

Error Handling with Flags

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
* Error handling using flags WORKING-STORAGE SECTION. 01 ERROR-FLAGS. 05 FILE-ERROR-FLAG PIC X VALUE "N". 88 FILE-ERROR VALUE "Y". 05 DATA-ERROR-FLAG PIC X VALUE "N". 88 DATA-ERROR VALUE "Y". 05 SYSTEM-ERROR-FLAG PIC X VALUE "N". 88 SYSTEM-ERROR VALUE "Y". 01 ERROR-MESSAGE PIC X(80). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF NOT FILE-ERROR PERFORM PROCESS-DATA END-IF IF NOT DATA-ERROR PERFORM FINALIZATION END-IF PERFORM ERROR-REPORTING STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" MOVE "Y" TO FILE-ERROR-FLAG MOVE "File open failed" TO ERROR-MESSAGE END-IF. PROCESS-DATA. PERFORM UNTIL FILE-ERROR OR DATA-ERROR READ CUSTOMER-FILE AT END EXIT PERFORM NOT AT END IF CUSTOMER-STATUS = "00" PERFORM VALIDATE-CUSTOMER ELSE MOVE "Y" TO FILE-ERROR-FLAG MOVE "File read error" TO ERROR-MESSAGE END-IF END-READ END-PERFORM. VALIDATE-CUSTOMER. IF CUSTOMER-ID = ZERO MOVE "Y" TO DATA-ERROR-FLAG MOVE "Invalid customer ID" TO ERROR-MESSAGE END-IF. ERROR-REPORTING. IF FILE-ERROR OR DATA-ERROR OR SYSTEM-ERROR DISPLAY "ERROR REPORT:" IF FILE-ERROR DISPLAY " File Error: " ERROR-MESSAGE END-IF IF DATA-ERROR DISPLAY " Data Error: " ERROR-MESSAGE END-IF IF SYSTEM-ERROR DISPLAY " System Error: " ERROR-MESSAGE END-IF ELSE DISPLAY "Program completed successfully" END-IF.

Using flags helps track different types of errors and control program flow.

Debugging Techniques

Effective debugging is essential for identifying and resolving errors in COBOL programs. Various techniques can help you trace program execution and identify problem areas.

Using DISPLAY for Debugging

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
* Debugging with DISPLAY statements IDENTIFICATION DIVISION. PROGRAM-ID. DEBUGPROG. WORKING-STORAGE SECTION. 01 DEBUG-FLAG PIC X VALUE "N". 88 DEBUG-MODE VALUE "Y". 01 DEBUG-COUNTER PIC 9(3) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. IF DEBUG-MODE DISPLAY "DEBUG: Entering INITIALIZATION" END-IF OPEN INPUT CUSTOMER-FILE IF DEBUG-MODE DISPLAY "DEBUG: File open status: " CUSTOMER-STATUS END-IF. PROCESS-DATA. PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END IF DEBUG-MODE ADD 1 TO DEBUG-COUNTER DISPLAY "DEBUG: Processing record " DEBUG-COUNTER DISPLAY "DEBUG: Customer ID: " CUSTOMER-ID END-IF PERFORM PROCESS-CUSTOMER END-READ END-PERFORM. PROCESS-CUSTOMER. IF DEBUG-MODE DISPLAY "DEBUG: Customer balance: " CUSTOMER-BALANCE END-IF IF CUSTOMER-BALANCE > 1000 IF DEBUG-MODE DISPLAY "DEBUG: High balance customer found" END-IF PERFORM PROCESS-HIGH-BALANCE END-IF. FINALIZATION. IF DEBUG-MODE DISPLAY "DEBUG: Entering FINALIZATION" DISPLAY "DEBUG: Total records processed: " DEBUG-COUNTER END-IF CLOSE CUSTOMER-FILE.

DISPLAY statements can be used to trace program execution and output variable values for debugging.

Conditional Debugging

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
* Conditional debugging with flags WORKING-STORAGE SECTION. 01 DEBUG-CONTROLS. 05 DEBUG-LEVEL PIC 9 VALUE 1. 88 DEBUG-BASIC VALUE 1. 88 DEBUG-DETAILED VALUE 2. 88 DEBUG-VERBOSE VALUE 3. 05 DEBUG-FILE-FLAG PIC X VALUE "N". 88 DEBUG-FILE VALUE "Y". 05 DEBUG-DATA-FLAG PIC X VALUE "N". 88 DEBUG-DATA VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. IF DEBUG-BASIC DISPLAY "DEBUG: Program started" END-IF OPEN INPUT CUSTOMER-FILE IF DEBUG-FILE DISPLAY "DEBUG: File open status: " CUSTOMER-STATUS END-IF. PROCESS-DATA. PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END IF DEBUG-DETAILED DISPLAY "DEBUG: Processing customer " CUSTOMER-ID END-IF PERFORM PROCESS-CUSTOMER END-READ END-PERFORM. PROCESS-CUSTOMER. IF DEBUG-DATA DISPLAY "DEBUG: Customer data:" DISPLAY " ID: " CUSTOMER-ID DISPLAY " Name: " CUSTOMER-NAME DISPLAY " Balance: " CUSTOMER-BALANCE END-IF IF DEBUG-VERBOSE DISPLAY "DEBUG: Performing calculations..." END-IF PERFORM CALCULATE-INTEREST. FINALIZATION. IF DEBUG-BASIC DISPLAY "DEBUG: Program completed" END-IF.

Using debug flags allows you to control the level of debugging output without modifying the code.

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
68
69
70
71
72
73
74
75
76
* Error logging and tracking IDENTIFICATION DIVISION. PROGRAM-ID. ERRORLOG. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ERROR-LOG-FILE ASSIGN TO "ERROR.LOG" ORGANIZATION IS LINE SEQUENTIAL FILE STATUS IS LOG-STATUS. DATA DIVISION. FILE SECTION. FD ERROR-LOG-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 01 ERROR-LOG-RECORD. 05 LOG-TIMESTAMP PIC X(20). 05 LOG-ERROR-CODE PIC XX. 05 LOG-ERROR-MSG PIC X(60). 05 LOG-PROGRAM-ID PIC X(8). WORKING-STORAGE SECTION. 01 LOG-STATUS PIC XX. 01 CURRENT-TIME PIC X(20). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-DATA PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN EXTEND ERROR-LOG-FILE IF LOG-STATUS NOT = "00" DISPLAY "WARNING: Cannot open error log file" END-IF. LOG-ERROR. MOVE FUNCTION CURRENT-DATE TO CURRENT-TIME MOVE CURRENT-TIME TO LOG-TIMESTAMP MOVE FILE-STATUS TO LOG-ERROR-CODE MOVE ERROR-MESSAGE TO LOG-ERROR-MSG MOVE "ERRORLOG" TO LOG-PROGRAM-ID WRITE ERROR-LOG-RECORD IF LOG-STATUS NOT = "00" DISPLAY "WARNING: Error logging failed" END-IF. PROCESS-DATA. OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" MOVE "File open failed" TO ERROR-MESSAGE PERFORM LOG-ERROR STOP RUN END-IF PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END IF CUSTOMER-STATUS NOT = "00" MOVE "File read error" TO ERROR-MESSAGE PERFORM LOG-ERROR ELSE PERFORM PROCESS-CUSTOMER END-IF END-READ END-PERFORM. FINALIZATION. CLOSE CUSTOMER-FILE CLOSE ERROR-LOG-FILE.

Error logging creates a permanent record of errors for analysis and debugging.

Data Validation and Error Prevention

Preventing errors through data validation is often more effective than handling them after they occur. COBOL provides various techniques for validating data before processing.

Input Validation

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
* Comprehensive input validation IDENTIFICATION DIVISION. PROGRAM-ID. VALIDATE. WORKING-STORAGE SECTION. 01 INPUT-DATA. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-AGE PIC 9(3). 05 CUSTOMER-SALARY PIC 9(7)V99. 01 VALIDATION-FLAGS. 05 ID-VALID PIC X VALUE "N". 88 VALID-ID VALUE "Y". 05 NAME-VALID PIC X VALUE "N". 88 VALID-NAME VALUE "Y". 05 AGE-VALID PIC X VALUE "N". 88 VALID-AGE VALUE "Y". 05 SALARY-VALID PIC X VALUE "N". 88 VALID-SALARY VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM GET-INPUT PERFORM VALIDATE-INPUT IF VALID-ID AND VALID-NAME AND VALID-AGE AND VALID-SALARY PERFORM PROCESS-VALID-DATA ELSE PERFORM DISPLAY-VALIDATION-ERRORS END-IF STOP RUN. GET-INPUT. DISPLAY "Enter Customer ID (5 digits): " ACCEPT CUSTOMER-ID DISPLAY "Enter Customer Name: " ACCEPT CUSTOMER-NAME DISPLAY "Enter Customer Age: " ACCEPT CUSTOMER-AGE DISPLAY "Enter Customer Salary: " ACCEPT CUSTOMER-SALARY. VALIDATE-INPUT. PERFORM VALIDATE-CUSTOMER-ID PERFORM VALIDATE-CUSTOMER-NAME PERFORM VALIDATE-CUSTOMER-AGE PERFORM VALIDATE-CUSTOMER-SALARY. VALIDATE-CUSTOMER-ID. IF CUSTOMER-ID > 0 AND CUSTOMER-ID <= 99999 MOVE "Y" TO ID-VALID ELSE MOVE "N" TO ID-VALID DISPLAY "ERROR: Invalid Customer ID" END-IF. VALIDATE-CUSTOMER-NAME. IF CUSTOMER-NAME NOT = SPACES AND FUNCTION LENGTH(FUNCTION TRIM(CUSTOMER-NAME)) > 0 MOVE "Y" TO NAME-VALID ELSE MOVE "N" TO NAME-VALID DISPLAY "ERROR: Customer name cannot be empty" END-IF. VALIDATE-CUSTOMER-AGE. IF CUSTOMER-AGE >= 18 AND CUSTOMER-AGE <= 120 MOVE "Y" TO AGE-VALID ELSE MOVE "N" TO AGE-VALID DISPLAY "ERROR: Age must be between 18 and 120" END-IF. VALIDATE-CUSTOMER-SALARY. IF CUSTOMER-SALARY > 0 AND CUSTOMER-SALARY <= 9999999.99 MOVE "Y" TO SALARY-VALID ELSE MOVE "N" TO SALARY-VALID DISPLAY "ERROR: Invalid salary amount" END-IF. DISPLAY-VALIDATION-ERRORS. DISPLAY "VALIDATION ERRORS:" IF NOT VALID-ID DISPLAY " - Invalid Customer ID" END-IF IF NOT VALID-NAME DISPLAY " - Invalid Customer Name" END-IF IF NOT VALID-AGE DISPLAY " - Invalid Age" END-IF IF NOT VALID-SALARY DISPLAY " - Invalid Salary" END-IF. PROCESS-VALID-DATA. DISPLAY "All data is valid - processing..."

Comprehensive input validation prevents invalid data from causing processing errors.

Range and Format Validation

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
* Range and format validation examples WORKING-STORAGE SECTION. 01 VALIDATION-RULES. 05 MIN-AGE PIC 9(3) VALUE 18. 05 MAX-AGE PIC 9(3) VALUE 120. 05 MIN-SALARY PIC 9(7)V99 VALUE 0.01. 05 MAX-SALARY PIC 9(7)V99 VALUE 9999999.99. 01 FORMAT-PATTERNS. 05 VALID-EMAIL PIC X(50) VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789@._-". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM VALIDATE-DATA STOP RUN. VALIDATE-DATA. PERFORM VALIDATE-NUMERIC-RANGES PERFORM VALIDATE-STRING-FORMATS PERFORM VALIDATE-DATE-FORMATS. VALIDATE-NUMERIC-RANGES. IF CUSTOMER-AGE < MIN-AGE OR CUSTOMER-AGE > MAX-AGE DISPLAY "ERROR: Age out of range (" MIN-AGE " to " MAX-AGE ")" END-IF IF CUSTOMER-SALARY < MIN-SALARY OR CUSTOMER-SALARY > MAX-SALARY DISPLAY "ERROR: Salary out of range" END-IF. VALIDATE-STRING-FORMATS. * Check for valid characters in email INSPECT CUSTOMER-EMAIL TALLYING INVALID-CHAR-COUNT FOR ALL CHARACTERS NOT IN VALID-EMAIL END-INSPECT IF INVALID-CHAR-COUNT > 0 DISPLAY "ERROR: Invalid characters in email address" END-IF. VALIDATE-DATE-FORMATS. * Validate date format (MMDDYYYY) IF BIRTH-DATE(1:2) < "01" OR BIRTH-DATE(1:2) > "12" DISPLAY "ERROR: Invalid month in birth date" END-IF IF BIRTH-DATE(3:2) < "01" OR BIRTH-DATE(3:2) > "31" DISPLAY "ERROR: Invalid day in birth date" END-IF IF BIRTH-DATE(5:4) < "1900" OR BIRTH-DATE(5:4) > "2023" DISPLAY "ERROR: Invalid year in birth date" END-IF.

Range and format validation ensures data meets specific requirements before processing.

Best Practices and Guidelines

Following established best practices ensures robust error handling and maintainable COBOL programs.

Error Handling Best Practices

  • Always check file status codes after file operations
  • Use appropriate error handling clauses (AT END, INVALID KEY, ON OVERFLOW)
  • Implement comprehensive data validation before processing
  • Provide meaningful error messages that help users understand the problem
  • Log errors appropriately for debugging and audit purposes
  • Handle all possible error conditions gracefully
  • Use structured error handling with EVALUATE statements
  • Maintain error flags and counters for monitoring
  • Implement proper cleanup procedures in error situations
  • Test error conditions thoroughly during development

Debugging Best Practices

  • Use conditional debugging with flags that can be easily enabled/disabled
  • Add strategic DISPLAY statements at key program points
  • Implement comprehensive logging of program execution and errors
  • Use meaningful variable names for debugging output
  • Create debug versions of programs for troubleshooting
  • Document debugging procedures for future reference
  • Use different debug levels for different types of information
  • Remove or disable debug code in production versions

Data Validation Best Practices

  • Validate all input data before processing
  • Check data ranges and formats according to business rules
  • Use consistent validation patterns throughout the program
  • Provide clear validation error messages to users
  • Implement both client-side and server-side validation
  • Use validation flags to track multiple validation errors
  • Document validation rules for maintenance
  • Test validation with edge cases and boundary conditions

Common Pitfalls to Avoid

  • Ignoring file status codes after file operations
  • Not handling end-of-file conditions in sequential reads
  • Forgetting to check for division by zero in arithmetic operations
  • Not validating input data before processing
  • Using generic error messages that don't help with debugging
  • Not implementing proper cleanup in error situations
  • Leaving debug code in production programs
  • Not testing error conditions during development
  • Using inconsistent error handling patterns throughout the program
  • Not documenting error handling procedures for maintenance

Test Your Knowledge

1. What is the primary purpose of file status codes in COBOL?

  • To provide detailed information about the result of file operations
  • To indicate program compilation errors
  • To show system resource usage
  • To display user input validation errors

2. Which file status code indicates a successful operation?

  • "10"
  • "00"
  • "23"
  • "30"

3. What does the INVALID KEY clause handle in COBOL?

  • File open errors
  • Record not found or duplicate key conditions
  • Syntax errors
  • Memory allocation errors

4. Which statement is used for structured error handling in COBOL?

  • IF-THEN-ELSE
  • EVALUATE
  • PERFORM
  • MOVE

5. What is the purpose of the ON OVERFLOW clause in STRING operations?

  • To handle end-of-file conditions
  • To handle when the target field is too small for the concatenated result
  • To handle file open errors
  • To handle division by zero errors

Frequently Asked Questions