MainframeMaster

COBOL Tutorial

COBOL File Status and Error Handling

Progress0 of 0 lessons

File Status Variables

File status variables are a critical component of robust COBOL file handling. They provide a standardized way to detect and respond to the results of file operations, allowing programs to handle both successful operations and various error conditions.

Declaring File Status

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD. 01 CUSTOMER-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 88 STATUS-SUCCESS VALUE "00". 88 END-OF-FILE VALUE "10". 88 FILE-NOT-FOUND VALUE "35".

  • FILE STATUS IS clause in the SELECT statement links the file to a status variable
  • The status variable must be defined as a two-character field (PIC XX)
  • 88-level condition names provide meaningful labels for common status codes
  • The status variable is automatically updated after each file operation

Basic Status Checking Pattern

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
* Method 1: Direct status code comparison OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS = "00" PERFORM PROCESS-FILE ELSE DISPLAY "Error opening file: " CUSTOMER-STATUS END-IF * Method 2: Using 88-level conditions OPEN INPUT CUSTOMER-FILE IF STATUS-SUCCESS PERFORM PROCESS-FILE ELSE IF FILE-NOT-FOUND DISPLAY "Customer file not found" PERFORM CREATE-EMPTY-FILE ELSE DISPLAY "Unexpected error: " CUSTOMER-STATUS END-IF * Method 3: Comprehensive condition handling OPEN INPUT CUSTOMER-FILE EVALUATE CUSTOMER-STATUS WHEN "00" PERFORM PROCESS-FILE WHEN "35" DISPLAY "File not found" PERFORM CREATE-EMPTY-FILE WHEN "37" DISPLAY "Access denied - check permissions" WHEN OTHER DISPLAY "Unexpected error: " CUSTOMER-STATUS END-EVALUATE

These examples demonstrate different approaches to checking file status. The 88-level conditions and EVALUATE statement make the code more readable and maintainable compared to direct status code comparisons.

Extended File Status

Some COBOL implementations support an extended file status, which provides more detailed information about 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
ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS EXTENDED-STATUS. DATA DIVISION. WORKING-STORAGE SECTION. 01 EXTENDED-STATUS. 05 PRIMARY-STATUS PIC XX. 88 STATUS-SUCCESS VALUE "00". 88 END-OF-FILE VALUE "10". 05 SECONDARY-STATUS PIC XXX. PROCEDURE DIVISION. MAIN-LOGIC. OPEN INPUT CUSTOMER-FILE IF NOT STATUS-SUCCESS DISPLAY "Error: " PRIMARY-STATUS "-" SECONDARY-STATUS * Secondary status provides more details about the error END-IF

The extended file status typically consists of the standard two-character status code plus additional implementation-specific details in the secondary status. This provides more granular information about errors, helping with troubleshooting.

Benefits of File Status Checking

  • Provides immediate feedback on the result of file operations
  • Allows programs to handle errors gracefully rather than terminating
  • Supports detailed error reporting and logging
  • Enables sophisticated error recovery strategies
  • Makes programs more robust and production-ready
  • Standardized approach across different file organizations
  • Helps diagnose issues during development and production

Common File Status Codes

COBOL file status codes follow a structured pattern. The first digit generally indicates the category of the status, while the second digit provides more specific information. Understanding these codes is essential for effective error handling.

Status Code Categories

First DigitCategoryDescription
0SuccessfulOperation completed normally
1At EndEnd of file or key range reached
2Invalid KeyKey-related issue (indexed/relative files)
3Permanent ErrorPhysical or hardware error
4Logic ErrorProgram or operation sequence error
9Implementor-DefinedImplementation-specific conditions

Common Status Codes for All File Types

StatusDescriptionOperationsHandling Approach
"00"Successful completionAll operationsContinue normal processing
"10"End of file reachedREADNormal condition; finalize processing
"35"File not foundOPEN INPUT, I-OCreate file or check path/name
"37"File access deniedOPENCheck permissions or file sharing
"39"File attribute conflictOPENCheck record definition or ASSIGN
"41"File already openOPENClose file before reopening
"42"File not openCLOSE, READ, WRITEOpen file before operation
"43"Required file access not takenDELETE, REWRITEREAD record before operation
"46"Read beyond file endREADReset file position or check logic
"47"File not open in required modeI/O operationsOpen file in correct mode
"48"File lockedI/O operationsWait and retry or check lock status
"90-99"Implementation-defined errorVariousCheck documentation for system

Status Codes Specific to Indexed Files

StatusDescriptionOperationsHandling Approach
"21"Key sequence errorWRITEEnsure records are in key sequence
"22"Duplicate keyWRITE, REWRITEUse unique key or update existing
"23"Record not foundREAD, REWRITE, DELETEVerify key or handle missing record
"24"Boundary violationWRITE, STARTCheck key range or record size

Defining Condition Names for Status Codes

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
WORKING-STORAGE SECTION. 01 FILE-STATUS-CODES. 05 CUSTOMER-STATUS PIC XX. * Success indicators 88 STATUS-OK VALUE "00". 88 END-OF-FILE VALUE "10". * Key-related errors 88 DUPLICATE-KEY VALUE "22". 88 RECORD-NOT-FOUND VALUE "23". * Open/access errors 88 FILE-NOT-FOUND VALUE "35". 88 ACCESS-DENIED VALUE "37". 88 FILE-ALREADY-OPEN VALUE "41". 88 FILE-NOT-OPEN VALUE "42". * General error classification 88 OPERATION-SUCCESS VALUE "00". 88 AT-END-CONDITION VALUE "10". 88 KEY-ERROR VALUE "21" "22" "23" "24". 88 PERMANENT-ERROR VALUE "30" THRU "39". 88 LOGIC-ERROR VALUE "40" THRU "49". 88 SERIOUS-ERROR VALUE "90" THRU "99". * Usage example READ CUSTOMER-FILE IF STATUS-OK PROCESS-RECORD ELSE IF END-OF-FILE PERFORM END-OF-PROCESSING ELSE IF RECORD-NOT-FOUND DISPLAY "Customer record not found" ELSE IF KEY-ERROR DISPLAY "Key error: " CUSTOMER-STATUS END-IF

Using 88-level condition names makes code more readable and self-documenting. It allows logical grouping of status codes by both specific conditions and general categories.

File Status Interpretation Guidelines

  • Always consult your COBOL implementation's documentation for exact status code meanings
  • Status "00" always means success, regardless of implementation
  • Status "10" always indicates end-of-file for READ operations
  • The 2x series always relates to key violations in indexed or relative files
  • The 4x series typically indicates program logic errors that can be corrected
  • The 9x series often indicates serious or unrecoverable errors
  • Status codes can vary slightly between COBOL implementations
  • Create a standardized approach to status code handling across programs

Error Recovery Techniques

Effective error recovery goes beyond simply detecting errors through file status. Robust COBOL programs implement strategies to handle, recover from, and continue processing despite file-related issues.

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
PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF NOT ERROR-OCCURRED PERFORM PROCESS-RECORDS UNTIL END-OF-FILE OR ERROR-OCCURRED END-IF PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE PERFORM CHECK-FILE-STATUS OPEN OUTPUT REPORT-FILE PERFORM CHECK-FILE-STATUS. PROCESS-RECORDS. READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ PERFORM CHECK-FILE-STATUS IF NOT END-OF-FILE AND NOT ERROR-OCCURRED PERFORM PROCESS-CUSTOMER END-IF. CHECK-FILE-STATUS. EVALUATE TRUE WHEN STATUS-OK CONTINUE WHEN END-OF-FILE IF NOT CUSTOMER-OPERATION * End of file only valid for reads DISPLAY "Unexpected end of file" SET ERROR-OCCURRED TO TRUE END-IF WHEN FILE-NOT-FOUND DISPLAY "File not found: " CURRENT-FILE SET ERROR-OCCURRED TO TRUE WHEN OTHER DISPLAY "File error " FILE-STATUS " on " CURRENT-FILE DISPLAY "Operation: " CURRENT-OPERATION SET ERROR-OCCURRED TO TRUE END-EVALUATE.

A centralized error handling routine simplifies code maintenance and ensures consistent error handling throughout the program. The CHECK-FILE-STATUS paragraph is called after each file operation.

Automatic Retry for Transient 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
WORKING-STORAGE SECTION. 01 RETRY-VARIABLES. 05 RETRY-COUNTER PIC 9(3) VALUE ZERO. 05 MAX-RETRIES PIC 9(3) VALUE 3. 05 RETRY-DELAY PIC 9(3) VALUE 2. PROCEDURE DIVISION. FILE-OPERATION-WITH-RETRY. MOVE ZERO TO RETRY-COUNTER PERFORM UNTIL RETRY-COUNTER > MAX-RETRIES OR STATUS-OK ADD 1 TO RETRY-COUNTER * Attempt the file operation OPEN I-O CUSTOMER-FILE EVALUATE TRUE WHEN STATUS-OK CONTINUE WHEN FILE-LOCKED IF RETRY-COUNTER < MAX-RETRIES DISPLAY "File locked, retry " RETRY-COUNTER " of " MAX-RETRIES CALL "C$SLEEP" USING RETRY-DELAY ELSE DISPLAY "Maximum retries exceeded" END-IF WHEN OTHER * Non-retryable error DISPLAY "Fatal error: " FILE-STATUS MOVE MAX-RETRIES TO RETRY-COUNTER END-EVALUATE END-PERFORM.

This pattern implements an automatic retry mechanism for transient errors such as file locks in a multi-user environment. It includes a delay between attempts and limits the number of retries.

Alternative Processing Paths

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
* Example: Handling a missing master file by using backup PERFORM OPEN-MASTER-FILE IF FILE-NOT-FOUND DISPLAY "Primary file not found, trying backup file" PERFORM OPEN-BACKUP-FILE IF STATUS-OK SET USING-BACKUP TO TRUE PERFORM LOG-BACKUP-USAGE ELSE DISPLAY "Cannot open primary or backup file" SET FATAL-ERROR TO TRUE END-IF END-IF * Example: Creating a file if it doesn't exist OPEN I-O TRANSACTION-LOG IF FILE-NOT-FOUND DISPLAY "Transaction log not found, creating new file" CLOSE TRANSACTION-LOG OPEN OUTPUT TRANSACTION-LOG IF STATUS-OK PERFORM WRITE-LOG-HEADER CLOSE TRANSACTION-LOG OPEN I-O TRANSACTION-LOG END-IF END-IF * Example: Skipping bad records and continuing PERFORM UNTIL END-OF-FILE READ INPUT-FILE AT END SET END-OF-FILE TO TRUE END-READ IF NOT END-OF-FILE IF VALID-RECORD PERFORM PROCESS-RECORD ELSE ADD 1 TO ERROR-RECORD-COUNT PERFORM WRITE-TO-ERROR-FILE END-IF END-IF END-PERFORM

These examples demonstrate different recovery strategies: falling back to backup files, automatically creating missing files, and skipping bad records to continue processing.

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
68
69
70
71
72
73
74
75
76
IDENTIFICATION DIVISION. PROGRAM-ID. ERRORLOG. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ERROR-LOG ASSIGN TO "ERRORLOG.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ERROR-LOG RECORD CONTAINS 200 CHARACTERS. 01 ERROR-RECORD PIC X(200). WORKING-STORAGE SECTION. 01 ERROR-LOG-FIELDS. 05 LOG-TIMESTAMP PIC X(26). 05 LOG-PROGRAM-ID PIC X(8). 05 LOG-FILE-NAME PIC X(30). 05 LOG-OPERATION PIC X(10). 05 LOG-STATUS-CODE PIC XX. 05 LOG-RECORD-KEY PIC X(20). 05 LOG-MESSAGE PIC X(100). 01 ERROR-LOG-RECORD. 05 LOG-DATETIME PIC X(26). 05 FILLER PIC X VALUE '|'. 05 LOG-PROGRAM PIC X(8). 05 FILLER PIC X VALUE '|'. 05 LOG-FILE PIC X(30). 05 FILLER PIC X VALUE '|'. 05 LOG-OPER PIC X(10). 05 FILLER PIC X VALUE '|'. 05 LOG-STATUS PIC XX. 05 FILLER PIC X VALUE '|'. 05 LOG-KEY PIC X(20). 05 FILLER PIC X VALUE '|'. 05 LOG-MSG PIC X(100). PROCEDURE DIVISION. LOG-FILE-ERROR. * Get current date and time MOVE FUNCTION CURRENT-DATE TO LOG-TIMESTAMP * Set log fields from parameters MOVE "CUSTMAIN" TO LOG-PROGRAM-ID MOVE "CUSTOMER.DAT" TO LOG-FILE-NAME MOVE "READ" TO LOG-OPERATION MOVE "23" TO LOG-STATUS-CODE MOVE "12345" TO LOG-RECORD-KEY MOVE "Customer record not found" TO LOG-MESSAGE * Format the log record PERFORM FORMAT-LOG-RECORD * Write to log file PERFORM WRITE-LOG-RECORD . FORMAT-LOG-RECORD. MOVE LOG-TIMESTAMP TO LOG-DATETIME MOVE LOG-PROGRAM-ID TO LOG-PROGRAM MOVE LOG-FILE-NAME TO LOG-FILE MOVE LOG-OPERATION TO LOG-OPER MOVE LOG-STATUS-CODE TO LOG-STATUS MOVE LOG-RECORD-KEY TO LOG-KEY MOVE LOG-MESSAGE TO LOG-MSG . WRITE-LOG-RECORD. OPEN EXTEND ERROR-LOG WRITE ERROR-RECORD FROM ERROR-LOG-RECORD CLOSE ERROR-LOG .

A robust error logging system captures detailed information about each error, including timestamp, program ID, file name, operation, status code, record key, and a descriptive message. This information is invaluable for troubleshooting.

Recovery Strategies for Specific Errors

Error ConditionStatus CodeRecovery Strategy
File not found"35"Create file, use backup, or alert user
Duplicate key"22"Generate unique key or update existing record
Record not found"23"Create default record or skip processing
File locked"48"Implement retry mechanism with timeout
Disk full"34"Free space, use alternate location, or compress
Hardware error"30"Notify operations, use disaster recovery plan

AT END and INVALID KEY Clauses

COBOL provides two key structured error handling mechanisms for file operations: the AT END clause for sequential access and the INVALID KEY clause for indexed and relative files. These clauses complement file status checking and provide inline error handling.

AT END Clause

The AT END clause handles the condition when a READ operation attempts to read beyond the end of a file. This is commonly used with sequential file 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
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
* Basic AT END structure READ CUSTOMER-FILE INTO WS-CUSTOMER-RECORD AT END SET END-OF-FILE TO TRUE NOT AT END ADD 1 TO RECORD-COUNT PERFORM PROCESS-CUSTOMER END-READ * Complete example with AT END IDENTIFICATION DIVISION. PROGRAM-ID. ATENDEXMP. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD. 01 CUSTOMER-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 WS-CUSTOMER-RECORD PIC X(100). 01 CUSTOMER-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 01 RECORD-COUNT PIC 9(5) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL END-OF-FILE PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening file: " CUSTOMER-STATUS MOVE "Y" TO EOF-FLAG END-IF. PROCESS-RECORDS. READ CUSTOMER-FILE INTO WS-CUSTOMER-RECORD AT END SET END-OF-FILE TO TRUE DISPLAY "End of file reached" NOT AT END ADD 1 TO RECORD-COUNT DISPLAY "Processing record " RECORD-COUNT END-READ * Check status for other errors IF NOT END-OF-FILE AND CUSTOMER-STATUS NOT = "00" DISPLAY "Error reading file: " CUSTOMER-STATUS MOVE "Y" TO EOF-FLAG END-IF. TERMINATION. CLOSE CUSTOMER-FILE DISPLAY "Total records processed: " RECORD-COUNT.

  • AT END executes when the file pointer is positioned after the last record
  • NOT AT END executes when a record is successfully read
  • END-READ terminates the scope of the READ statement
  • AT END sets file status to "10" automatically
  • Additional file status checking can detect other errors

INVALID KEY Clause

The INVALID KEY clause handles key-related errors in indexed and relative files, such as record not found, duplicate key, or boundary violations.

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
* Basic INVALID KEY structure READ CUSTOMER-FILE KEY IS CUSTOMER-ID INVALID KEY DISPLAY "Customer " CUSTOMER-ID " not found" NOT INVALID KEY PERFORM PROCESS-CUSTOMER END-READ * INVALID KEY with WRITE WRITE CUSTOMER-RECORD INVALID KEY EVALUATE CUSTOMER-STATUS WHEN "22" DISPLAY "Duplicate customer ID: " CUSTOMER-ID WHEN "24" DISPLAY "Key out of allowed range" WHEN OTHER DISPLAY "Error: " CUSTOMER-STATUS END-EVALUATE NOT INVALID KEY ADD 1 TO RECORDS-ADDED END-WRITE * Complete example with INVALID KEY IDENTIFICATION DIVISION. PROGRAM-ID. INVKEYEXMP. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.IDX" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUST-ID FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(5). 05 CUST-NAME PIC X(30). 05 CUST-ADDRESS PIC X(50). 05 CUST-BALANCE PIC S9(7)V99. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 SEARCH-ID PIC 9(5). 01 VALID-DATA PIC X VALUE "Y". 01 PROCESSING-FLAG PIC X VALUE "Y". 88 CONTINUE-PROCESSING VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM UNTIL NOT CONTINUE-PROCESSING DISPLAY "Enter customer ID (0 to quit): " ACCEPT SEARCH-ID IF SEARCH-ID = 0 MOVE "N" TO PROCESSING-FLAG ELSE PERFORM LOOKUP-CUSTOMER END-IF END-PERFORM PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN I-O CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening file: " CUSTOMER-STATUS MOVE "N" TO PROCESSING-FLAG END-IF. LOOKUP-CUSTOMER. MOVE SEARCH-ID TO CUST-ID READ CUSTOMER-FILE INVALID KEY EVALUATE CUSTOMER-STATUS WHEN "23" DISPLAY "Customer " SEARCH-ID " not found" DISPLAY "Would you like to add this customer? (Y/N)" ACCEPT VALID-DATA IF VALID-DATA = "Y" PERFORM ADD-NEW-CUSTOMER END-IF WHEN OTHER DISPLAY "Error: " CUSTOMER-STATUS END-EVALUATE NOT INVALID KEY DISPLAY "Customer found: " CUST-NAME DISPLAY "Balance: " CUST-BALANCE END-READ. ADD-NEW-CUSTOMER. MOVE SEARCH-ID TO CUST-ID DISPLAY "Enter customer name: " ACCEPT CUST-NAME DISPLAY "Enter customer address: " ACCEPT CUST-ADDRESS MOVE ZERO TO CUST-BALANCE WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error adding customer: " CUSTOMER-STATUS NOT INVALID KEY DISPLAY "Customer added successfully" END-WRITE. TERMINATION. CLOSE CUSTOMER-FILE.

  • INVALID KEY executes when a key-related error occurs
  • NOT INVALID KEY executes when the operation is successful
  • Applies to READ, WRITE, REWRITE, DELETE, and START operations
  • Automatically sets appropriate file status codes (e.g., "22", "23")
  • Can be combined with status checking for detailed error handling

Combining Clauses with File Status

For comprehensive error handling, combine AT END/INVALID KEY clauses with file status checking. This ensures that both expected conditions and unexpected errors are properly handled.

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
* Example with both mechanisms READ CUSTOMER-FILE NEXT RECORD AT END SET END-OF-FILE TO TRUE NOT AT END ADD 1 TO RECORD-COUNT END-READ * Check for other errors IF NOT END-OF-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error reading file: " CUSTOMER-STATUS PERFORM ERROR-HANDLING-ROUTINE ELSE PERFORM PROCESS-RECORD END-IF END-IF * Example for indexed file READ CUSTOMER-FILE KEY IS CUSTOMER-ID INVALID KEY IF CUSTOMER-STATUS = "23" DISPLAY "Customer " CUSTOMER-ID " not found" ELSE DISPLAY "Unexpected key error: " CUSTOMER-STATUS END-IF END-READ * Additional status check for unexpected errors IF CUSTOMER-STATUS NOT = "00" AND CUSTOMER-STATUS NOT = "23" DISPLAY "Serious error occurred: " CUSTOMER-STATUS PERFORM ERROR-RECOVERY-ROUTINE END-IF

This pattern provides the most comprehensive error handling. The clauses handle expected conditions (end of file, record not found), while the file status checks catch any other unexpected errors.

Comparing Error Handling Approaches

ApproachAdvantagesLimitationsBest For
File Status OnlyCatches all error types, Centralized handlingMore verbose code, Separated from file operationComplex error recovery logic
AT END / INVALID KEYInline with operation, More readableLimited to specific error typesExpected conditions in routine processing
Combined ApproachComprehensive, Handles all scenariosMore complex code structureProduction systems requiring robust handling
88-Level ConditionsReadable code, Self-documentingRequires additional definitionsAny approach for improved readability

Proper File Exception Handling

Proper file exception handling in COBOL combines all the techniques we've discussed into a comprehensive approach. This ensures that programs can detect, report, and recover from a wide range of file-related issues while maintaining data integrity.

Best Practices for File Exception Handling

  • Check file status after EVERY file operation - Never assume success
  • Use 88-level condition names - Makes code more readable and maintainable
  • Implement both structured clauses and status checking - For comprehensive coverage
  • Create a centralized error handling module - Ensures consistent handling
  • Log detailed error information - Include operation, file, status, and context
  • Implement graceful degradation - Allow partial processing when possible
  • Close files properly even after errors - Prevents resource leaks
  • Use appropriate recovery strategies - Based on specific error conditions
  • Consider transaction processing - For related updates requiring consistency
  • Include file status in all error messages - Aids in troubleshooting

Common Pitfalls to Avoid

PitfallConsequenceBetter Approach
Ignoring file statusUndetected errors, data corruptionCheck status after every operation
Relying only on AT END / INVALID KEYMissing non-standard errorsCombine with status checking
Generic error handlingLimited recovery optionsError-specific recovery strategies
Not closing files after errorsResource leaks, locked filesClose files in termination routine
Poor error messagesDifficult troubleshootingInclude operation, file, and status
Not validating input dataPreventable errorsValidate before file operations

Comprehensive File Handling 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
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
IDENTIFICATION DIVISION. PROGRAM-ID. FILEHDLR. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.IDX" ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUST-ID ALTERNATE RECORD KEY IS CUST-NAME WITH DUPLICATES FILE STATUS IS CUSTOMER-STATUS. SELECT ERROR-LOG ASSIGN TO "ERRORLOG.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS LOG-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(5). 05 CUST-NAME PIC X(30). 05 CUST-ADDRESS PIC X(50). 05 CUST-BALANCE PIC S9(7)V99. FD ERROR-LOG LABEL RECORDS ARE STANDARD. 01 LOG-RECORD PIC X(200). WORKING-STORAGE SECTION. 01 FILE-STATUS-FIELDS. 05 CUSTOMER-STATUS PIC XX. 88 CUST-SUCCESS VALUE "00". 88 CUST-EOF VALUE "10". 88 CUST-DUPLICATE VALUE "22". 88 CUST-NOT-FOUND VALUE "23". 88 CUST-NOT-EXISTS VALUE "35". 05 LOG-STATUS PIC XX. 05 CURRENT-FILE PIC X(30) VALUE SPACES. 05 CURRENT-OPERATION PIC X(10) VALUE SPACES. 01 PROGRAM-FLAGS. 05 ERROR-FLAG PIC X VALUE "N". 88 ERROR-OCCURRED VALUE "Y". 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 05 RETRY-COUNTER PIC 9(3) VALUE ZERO. 05 MAX-RETRIES PIC 9(3) VALUE 3. 01 SEARCH-ID PIC 9(5). 01 LOG-FIELDS. 05 LOG-TIMESTAMP PIC X(26). 05 LOG-FORMATTED PIC X(200). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF NOT ERROR-OCCURRED PERFORM PROCESS-RECORDS UNTIL END-OF-FILE OR ERROR-OCCURRED END-IF PERFORM TERMINATION STOP RUN. INITIALIZATION. MOVE "CUSTOMER.IDX" TO CURRENT-FILE MOVE "OPEN" TO CURRENT-OPERATION OPEN I-O CUSTOMER-FILE PERFORM CHECK-FILE-STATUS IF CUST-NOT-EXISTS DISPLAY "Customer file not found. Creating new file." CLOSE CUSTOMER-FILE OPEN OUTPUT CUSTOMER-FILE PERFORM CHECK-FILE-STATUS IF NOT ERROR-OCCURRED CLOSE CUSTOMER-FILE OPEN I-O CUSTOMER-FILE PERFORM CHECK-FILE-STATUS END-IF END-IF. PROCESS-RECORDS. DISPLAY "Enter customer ID (0 to quit): " ACCEPT SEARCH-ID IF SEARCH-ID = ZERO SET END-OF-FILE TO TRUE ELSE PERFORM READ-CUSTOMER IF NOT ERROR-OCCURRED IF CUST-NOT-FOUND DISPLAY "Customer not found. Add new customer? (Y/N)" ACCEPT EOF-FLAG IF EOF-FLAG = "Y" PERFORM ADD-CUSTOMER END-IF ELSE DISPLAY "Customer found: " CUST-NAME DISPLAY "Balance: " CUST-BALANCE DISPLAY "Update this customer? (Y/N)" ACCEPT EOF-FLAG IF EOF-FLAG = "Y" PERFORM UPDATE-CUSTOMER END-IF END-IF END-IF END-IF. READ-CUSTOMER. MOVE "READ" TO CURRENT-OPERATION MOVE SEARCH-ID TO CUST-ID READ CUSTOMER-FILE INVALID KEY IF CUST-NOT-FOUND CONTINUE ELSE PERFORM LOG-ERROR END-IF END-READ PERFORM CHECK-FILE-STATUS. ADD-CUSTOMER. MOVE "WRITE" TO CURRENT-OPERATION MOVE SEARCH-ID TO CUST-ID DISPLAY "Enter customer name: " ACCEPT CUST-NAME DISPLAY "Enter customer address: " ACCEPT CUST-ADDRESS MOVE ZERO TO CUST-BALANCE WRITE CUSTOMER-RECORD INVALID KEY PERFORM LOG-ERROR NOT INVALID KEY DISPLAY "Customer added successfully" END-WRITE PERFORM CHECK-FILE-STATUS. UPDATE-CUSTOMER. MOVE "REWRITE" TO CURRENT-OPERATION DISPLAY "Enter new customer name (or ENTER to keep): " ACCEPT EOF-FLAG IF EOF-FLAG NOT = SPACES MOVE EOF-FLAG TO CUST-NAME END-IF DISPLAY "Enter new address (or ENTER to keep): " ACCEPT EOF-FLAG IF EOF-FLAG NOT = SPACES MOVE EOF-FLAG TO CUST-ADDRESS END-IF DISPLAY "Enter new balance (or ENTER to keep): " ACCEPT EOF-FLAG IF EOF-FLAG NOT = SPACES MOVE FUNCTION NUMVAL(EOF-FLAG) TO CUST-BALANCE END-IF REWRITE CUSTOMER-RECORD INVALID KEY PERFORM LOG-ERROR NOT INVALID KEY DISPLAY "Customer updated successfully" END-REWRITE PERFORM CHECK-FILE-STATUS. CHECK-FILE-STATUS. EVALUATE TRUE WHEN CUST-SUCCESS CONTINUE WHEN CUST-EOF SET END-OF-FILE TO TRUE WHEN CUST-NOT-FOUND * Not an error for our program logic CONTINUE WHEN OTHER PERFORM LOG-ERROR END-EVALUATE. LOG-ERROR. SET ERROR-OCCURRED TO TRUE DISPLAY "Error on " CURRENT-OPERATION " for " CURRENT-FILE DISPLAY "Status code: " CUSTOMER-STATUS * Log error to file MOVE FUNCTION CURRENT-DATE TO LOG-TIMESTAMP STRING LOG-TIMESTAMP DELIMITED BY SIZE " | FILEHDLR | " CURRENT-FILE DELIMITED BY SPACE " | " DELIMITED BY SIZE CURRENT-OPERATION DELIMITED BY SPACE " | " DELIMITED BY SIZE CUSTOMER-STATUS DELIMITED BY SIZE " | " DELIMITED BY SIZE "Cust ID: " DELIMITED BY SIZE CUST-ID DELIMITED BY SIZE INTO LOG-FORMATTED END-STRING MOVE "ERRORLOG.DAT" TO CURRENT-FILE MOVE "WRITE" TO CURRENT-OPERATION OPEN EXTEND ERROR-LOG IF LOG-STATUS = "00" MOVE LOG-FORMATTED TO LOG-RECORD WRITE LOG-RECORD CLOSE ERROR-LOG ELSE DISPLAY "Could not open error log" END-IF. TERMINATION. MOVE "CLOSE" TO CURRENT-OPERATION CLOSE CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Warning: Error closing " CURRENT-FILE DISPLAY "Status: " CUSTOMER-STATUS END-IF IF ERROR-OCCURRED DISPLAY "Program completed with errors" ELSE DISPLAY "Program completed successfully" END-IF.

This comprehensive example demonstrates best practices for file exception handling:

  • Status checking after every operation
  • Centralized error handling routine
  • Error logging to a separate file
  • Recovery strategies (creating missing files)
  • Proper file closing in termination
  • Using 88-level conditions for readability
  • Combining AT END/INVALID KEY with status checking
  • Detailed error information (operation, file, status)

File Handling in Multi-User Environments

In multi-user environments, additional considerations for file handling include:

  • Record locking - Preventing concurrent updates to the same record
  • File locking - Controlling access to an entire file
  • Deadlock prevention - Avoiding situations where processes wait for each other
  • Retry mechanisms - Handling temporary lock conditions
  • Transaction integrity - Ensuring related updates are atomic
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
* Example of retry logic for locked records PERFORM WITH TEST AFTER UNTIL STATUS-OK OR RETRY-COUNTER > MAX-RETRIES ADD 1 TO RETRY-COUNTER READ CUSTOMER-FILE WITH LOCK INVALID KEY PERFORM CHECK-INVALID-KEY END-READ IF CUSTOMER-STATUS = "48" OR CUSTOMER-STATUS = "9D" * Record or file is locked DISPLAY "Record locked, retry attempt " RETRY-COUNTER * Wait a moment before retrying CALL "C$SLEEP" USING 2 END-IF END-PERFORM IF RETRY-COUNTER > MAX-RETRIES DISPLAY "Maximum retries exceeded - record still locked" SET ERROR-OCCURRED TO TRUE END-IF

This example shows a retry mechanism for handling locked records in a multi-user environment. The program attempts to read the record multiple times with a delay between attempts.

Integration with System Recovery

Robust file exception handling should integrate with broader system recovery mechanisms:

  • Checkpoint/restart procedures - For recovering long-running processes
  • Backup and restore - For catastrophic failures
  • Transaction journals - For rolling back or forward after failures
  • Return codes - For communicating status to calling programs or JCL
  • Operational alerts - For notifying support staff of critical issues

By integrating file exception handling with these broader recovery mechanisms, COBOL programs can provide resilient and reliable file processing even in the face of various error conditions.

Test Your Knowledge

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

  • To allocate memory for file operations
  • To provide information on the result of file operations
  • To optimize the file for faster processing
  • To define file attributes in the FD entry

2. Which file status code indicates a successful file operation in COBOL?

  • "00"
  • "10"
  • "35"
  • "OK"

3. What is the file status code for "end of file reached" during a READ operation?

  • "00"
  • "10"
  • "23"
  • "40"

4. Which of the following is NOT a valid approach for handling file errors in COBOL?

  • Using the FILE STATUS clause in SELECT statements
  • Implementing the AT END clause for READ operations
  • Using the ACCEPT statement to retry failed operations automatically
  • Using the INVALID KEY clause for indexed file operations

5. What is the recommended practice for checking file status after operations?

  • Only check after operations that commonly fail
  • Check only the first character of the status code
  • Check status after every file operation
  • Check status only for write operations

Frequently Asked Questions