MainframeMaster

COBOL Tutorial

COBOL Sequential File Operations

Progress0 of 0 lessons

OPEN Statement (INPUT, OUTPUT, I-O, EXTEND)

The OPEN statement establishes a connection between a COBOL program and a file, making it available for processing. It is the first operation performed on a file before any other file operations can be executed. The mode used in the OPEN statement determines what operations are permitted on the file.

Basic Syntax

cobol
1
2
3
4
OPEN [INPUT file-name-1 [file-name-2] ...] [OUTPUT file-name-3 [file-name-4] ...] [I-O file-name-5 [file-name-6] ...] [EXTEND file-name-7 [file-name-8] ...]

Multiple files can be opened in a single OPEN statement, and different files can be opened with different modes in the same statement.

OPEN Modes

ModeDescriptionPermitted OperationsFile State
INPUTOpens an existing file for readingREADFile must exist
OUTPUTCreates a new file for writingWRITEAny existing file is deleted
I-OOpens an existing file for both reading and writingREAD, REWRITE, DELETEFile must exist
EXTENDOpens an existing file for adding records at the endWRITE (appends to end)File must exist

Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
* Opening a single file for reading OPEN INPUT CUSTOMER-FILE. * Opening multiple files with different modes OPEN INPUT CUSTOMER-MASTER OUTPUT REPORT-FILE I-O TRANSACTION-FILE. * Opening a file for appending records OPEN EXTEND LOG-FILE. * Combined with file status checking OPEN INPUT CUSTOMER-FILE IF CUSTOMER-FILE-STATUS = "00" PERFORM PROCESS-CUSTOMERS ELSE PERFORM FILE-ERROR-ROUTINE END-IF.

Common Errors and Solutions

ErrorStatus CodeCauseSolution
File not found"35"Opening a non-existent file with INPUT or I-OCreate file first or handle error
Access denied"37"Insufficient permissionsFix file permissions
File already open"41"Attempting to open a file already openedClose file before reopening
File attribute conflict"39"File characteristics don't match FDEnsure file and FD match

Best Practices

  • Always check the file status after OPEN operations
  • Use the appropriate mode for the intended operations
  • Consider using I-O instead of INPUT if you might need to update the file
  • Be cautious with OUTPUT mode as it erases existing files
  • Use EXTEND for log files and other append-only scenarios
  • Open files only when needed and close them as soon as possible
  • Include error handling for all possible file status codes

READ Statement for Sequential Files

The READ statement retrieves the next record from a sequential file. Each successful READ advances the file position to the following record. For sequential files, records are read in the order they were written, from the beginning to the end of the file.

Basic Syntax

cobol
1
2
3
4
READ file-name [NEXT] [RECORD] [INTO identifier] [AT END imperative-statement-1] [NOT AT END imperative-statement-2] [END-READ]

  • NEXT is optional for sequential files but required for indexed or relative files
  • RECORD is optional and has no functional effect
  • INTO transfers the record to a working-storage area
  • AT END specifies actions when the end of file is reached
  • NOT AT END specifies actions when a record is successfully read
  • END-READ terminates the scope of the READ statement

READ Variations

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
* Basic READ READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ. * READ with both AT END and NOT AT END READ EMPLOYEE-FILE AT END DISPLAY "End of file reached" MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO RECORD-COUNT PERFORM PROCESS-EMPLOYEE END-READ. * READ INTO a working-storage area READ TRANSACTION-FILE INTO TRANSACTION-WORK-RECORD AT END MOVE "Y" TO EOF-FLAG END-READ.

The INTO clause is particularly useful when you want to keep the file record separate from your working data, allowing you to maintain the original record while modifying a copy.

Typical Processing Loop

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. SEQREAD. 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 RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(5). 05 CUST-NAME PIC X(30). 05 CUST-ADDRESS PIC X(40). 05 CUST-TYPE PIC X. 88 RETAIL VALUE "R". 88 WHOLESALE VALUE "W". 88 GOVERNMENT VALUE "G". 05 FILLER PIC X(4). WORKING-STORAGE SECTION. 01 FILE-VARIABLES. 05 CUSTOMER-STATUS PIC XX. 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 01 COUNTERS. 05 RETAIL-COUNT PIC 9(5) VALUE ZEROS. 05 WHOLESALE-COUNT PIC 9(5) VALUE ZEROS. 05 GOVERNMENT-COUNT PIC 9(5) VALUE ZEROS. 05 TOTAL-COUNT PIC 9(5) VALUE ZEROS. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL END-OF-FILE PERFORM FINALIZATION 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 AT END MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO TOTAL-COUNT EVALUATE TRUE WHEN RETAIL ADD 1 TO RETAIL-COUNT WHEN WHOLESALE ADD 1 TO WHOLESALE-COUNT WHEN GOVERNMENT ADD 1 TO GOVERNMENT-COUNT END-EVALUATE END-READ. FINALIZATION. CLOSE CUSTOMER-FILE DISPLAY "Processing complete" DISPLAY "Total records: " TOTAL-COUNT DISPLAY "Retail customers: " RETAIL-COUNT DISPLAY "Wholesale customers: " WHOLESALE-COUNT DISPLAY "Government customers: " GOVERNMENT-COUNT.

This example demonstrates a typical sequential file processing pattern. It reads customer records, counts records by customer type, and displays totals when complete. The processing loop continues until the end of file is reached.

End of File Detection

There are two common methods to detect the end of a file:

  1. Using the AT END clause: This method executes specific code when the end of file is reached. Typically, it sets a flag that controls the main processing loop.
  2. Checking the file status: After each READ operation, check if the file status is "10" (end of file). This is especially useful when additional error conditions need to be handled.
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
* Method 1: Using AT END READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG END-READ. * Method 2: Checking file status READ CUSTOMER-FILE IF CUSTOMER-STATUS = "10" MOVE "Y" TO EOF-FLAG END-IF. * Combined approach (most robust) READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG END-READ IF CUSTOMER-STATUS NOT = "00" AND CUSTOMER-STATUS NOT = "10" DISPLAY "Error reading file: " CUSTOMER-STATUS PERFORM ERROR-ROUTINE END-IF.

Best Practices for READ Operations

  • Always include AT END handling with each READ statement
  • Use a flag (typically an 88-level condition) to control processing loops
  • Check file status after READ operations to detect errors
  • Use the NOT AT END clause for clearer code structure
  • Consider using READ...INTO when you need to preserve the original record
  • Never attempt to read past the end of file
  • Include proper error handling for all possible file status codes

WRITE Statement Basics

The WRITE statement adds new records to a file. For sequential files, each WRITE operation adds a record at the current position, which is typically at the end of the file. The position advances automatically after each WRITE, making records appear in the file in the same order they were written.

Basic Syntax

cobol
1
2
3
4
5
WRITE record-name [FROM identifier-1] [AFTER|BEFORE ADVANCING {identifier-2 | integer | PAGE}] [AT END-OF-PAGE imperative-statement-1] [NOT AT END-OF-PAGE imperative-statement-2] [END-WRITE]

  • record-name must be a record name defined in the FILE SECTION
  • FROM specifies data to be moved to the record before writing
  • ADVANCING controls line spacing for print files
  • END-OF-PAGE applies to print files (reports)
  • END-WRITE terminates the scope of the WRITE statement

Writing Records - Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
* Basic WRITE WRITE CUSTOMER-RECORD. * WRITE with FROM clause WRITE CUSTOMER-RECORD FROM CUSTOMER-WORK-AREA. * WRITE with file status checking WRITE EMPLOYEE-RECORD IF FILE-STATUS NOT = "00" PERFORM ERROR-ROUTINE END-IF. * WRITE for print files with line control WRITE REPORT-LINE AFTER ADVANCING 2 LINES. WRITE REPORT-LINE BEFORE ADVANCING PAGE. WRITE REPORT-LINE AFTER ADVANCING LINE-COUNT LINES.

The FROM clause is particularly useful as it allows you to write from a working-storage area while preserving the contents of the file record area for subsequent operations.

Complete Example: Creating a File

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
IDENTIFICATION DIVISION. PROGRAM-ID. FILEWRITE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT OUTPUT-FILE ASSIGN TO "NEWDATA.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD OUTPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 OUTPUT-RECORD. 05 REC-TYPE PIC X. 05 REC-ID PIC 9(5). 05 REC-NAME PIC X(30). 05 REC-AMOUNT PIC 9(7)V99. 05 REC-DATE PIC 9(8). 05 FILLER PIC X(28). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. 01 WS-RECORD. 05 WS-TYPE PIC X. 05 WS-ID PIC 9(5). 05 WS-NAME PIC X(30). 05 WS-AMOUNT PIC 9(7)V99. 05 WS-DATE PIC 9(8). 05 FILLER PIC X(28). 01 EOF-FLAG PIC X VALUE "N". 88 END-OF-DATA VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL END-OF-DATA PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN OUTPUT OUTPUT-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening output file: " FILE-STATUS MOVE "Y" TO EOF-FLAG END-IF. PROCESS-RECORDS. DISPLAY "Enter record type (or X to exit): " ACCEPT WS-TYPE IF WS-TYPE = "X" MOVE "Y" TO EOF-FLAG ELSE DISPLAY "Enter ID: " ACCEPT WS-ID DISPLAY "Enter Name: " ACCEPT WS-NAME DISPLAY "Enter Amount: " ACCEPT WS-AMOUNT DISPLAY "Enter Date (YYYYMMDD): " ACCEPT WS-DATE WRITE OUTPUT-RECORD FROM WS-RECORD IF FILE-STATUS NOT = "00" DISPLAY "Error writing record: " FILE-STATUS PERFORM ERROR-ROUTINE END-IF END-IF. TERMINATION. CLOSE OUTPUT-FILE DISPLAY "File processing complete.". ERROR-ROUTINE. DISPLAY "File operation failed with status: " FILE-STATUS DISPLAY "Processing terminated." MOVE "Y" TO EOF-FLAG.

This example demonstrates creating a sequential file by accepting user input and writing records until the user enters 'X' for the record type. It shows proper file opening, writing with the FROM clause, status checking, and closing.

WRITE Operations for Different OPEN Modes

OPEN ModeWRITE BehaviorCommon Use Case
OUTPUTWrites records to a new file, starting at the beginningCreating new files, replacing existing files
EXTENDAdds records to the end of an existing fileAppending to log files, adding to existing data
I-OWRITE is not allowed for sequential files in I-O modeN/A (Use REWRITE instead for updates)
INPUTWRITE is not allowed in INPUT modeN/A (Change to OUTPUT or EXTEND mode)

Error Handling for WRITE Operations

Status CodeError ConditionSolution
"24"Boundary violation (record size)Check record size matches FD
"34"Disk full or quota exceededFree disk space or increase quota
"48"WRITE not supported in current open modeChange OPEN mode to OUTPUT or EXTEND
"90"Other I/O error during writeCheck system logs, disk hardware

Best Practices for WRITE Operations

  • Check file status after every WRITE operation
  • Use the FROM clause when working with complex record structures
  • Validate data before writing to ensure data integrity
  • Ensure the file is opened in the appropriate mode (OUTPUT or EXTEND)
  • For large volumes, consider buffering multiple records before writing
  • Include proper error handling for disk-full and other error conditions
  • Test both successful writes and error conditions in your programs

CLOSE Statement

The CLOSE statement terminates the connection between a COBOL program and a file, releasing any resources associated with the file. It is important to properly close all files when processing is complete to ensure data integrity and prevent resource leaks.

Basic Syntax

cobol
1
CLOSE file-name-1 [file-name-2] ... [WITH LOCK]

  • Multiple files can be closed in a single CLOSE statement
  • WITH LOCK prevents the file from being reopened in the same program run
  • No special positioning clauses are needed for sequential files

Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
* Closing a single file CLOSE CUSTOMER-FILE. * Closing multiple files CLOSE CUSTOMER-FILE TRANSACTION-FILE REPORT-FILE. * Closing with lock CLOSE SENSITIVE-DATA-FILE WITH LOCK. * Closing with file status checking CLOSE INVENTORY-FILE IF INVENTORY-STATUS NOT = "00" PERFORM CLOSE-ERROR-ROUTINE END-IF.

File Closing Process

When a file is closed, the following actions typically occur:

  1. Any remaining buffers are flushed to the physical device
  2. File control blocks and buffers are released
  3. End-of-file markers or trailers are written if required
  4. System resources associated with the file are freed
  5. The file can no longer be accessed without reopening it

Proper closing is essential, especially for output files, to ensure all data is written to the physical device and file integrity is maintained.

Error Handling for CLOSE Operations

While CLOSE operations typically succeed, some errors can occur:

Status CodeError ConditionPossible Cause
"42"File not openAttempting to close a file that isn't open
"90-99"Physical I/O errorHardware issue during final write operations
"34"Disk fullNot enough space to write final buffers

Best Practices for CLOSE Operations

  • Always close files when processing is complete
  • Check file status after CLOSE operations
  • Close files in error handling routines
  • Use CLOSE WITH LOCK for sensitive files
  • Include CLOSE operations in program termination logic
  • Ensure files are properly opened before attempting to close them
  • Consider using a standardized file handling module to ensure consistent file closing

Example: Proper File Handling 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
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
IDENTIFICATION DIVISION. PROGRAM-ID. FILEOPS. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO "INPUT.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS INPUT-STATUS. SELECT OUTPUT-FILE ASSIGN TO "OUTPUT.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS OUTPUT-STATUS. DATA DIVISION. FILE SECTION. FD INPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 INPUT-RECORD PIC X(80). FD OUTPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 OUTPUT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUSES. 05 INPUT-STATUS PIC XX. 05 OUTPUT-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION IF INPUT-STATUS = "00" AND OUTPUT-STATUS = "00" PERFORM PROCESS-FILES UNTIL END-OF-FILE END-IF PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT INPUT-FILE IF INPUT-STATUS NOT = "00" DISPLAY "Error opening input file: " INPUT-STATUS MOVE "Y" TO EOF-FLAG ELSE OPEN OUTPUT OUTPUT-FILE IF OUTPUT-STATUS NOT = "00" DISPLAY "Error opening output file: " OUTPUT-STATUS MOVE "Y" TO EOF-FLAG * Close the file that was successfully opened CLOSE INPUT-FILE END-IF END-IF. PROCESS-FILES. READ INPUT-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END MOVE INPUT-RECORD TO OUTPUT-RECORD WRITE OUTPUT-RECORD IF OUTPUT-STATUS NOT = "00" DISPLAY "Error writing record: " OUTPUT-STATUS MOVE "Y" TO EOF-FLAG END-IF END-READ. TERMINATION. * Close files regardless of processing status IF INPUT-STATUS NOT = "42" * Not "file not open" CLOSE INPUT-FILE END-IF IF OUTPUT-STATUS NOT = "42" * Not "file not open" CLOSE OUTPUT-FILE END-IF DISPLAY "Processing complete." DISPLAY "Input status: " INPUT-STATUS DISPLAY "Output status: " OUTPUT-STATUS.

This example demonstrates robust file handling with proper opening, error detection, and closing. Note that the termination routine closes files even if errors occurred during processing, ensuring that resources are properly released.

File Status Checking

File status checking is an essential aspect of COBOL file handling. The file status is a two-character field that contains the result of each file operation. By checking this status after each operation, programs can detect and handle errors or exceptional conditions.

Defining File Status

File status is defined in two places:

  1. In the SELECT statement of the ENVIRONMENT DIVISION (FILE STATUS clause)
  2. As a two-character field in WORKING-STORAGE
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
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. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 88 STATUS-OK VALUE "00". 88 END-OF-FILE VALUE "10". 88 FILE-NOT-FOUND VALUE "35".

Using 88-level condition names makes the code more readable when checking for specific status conditions.

Common File Status Codes

StatusMeaningOperations
"00"Successful completionAll operations
"10"End of file reachedREAD
"35"File not foundOPEN INPUT, OPEN I-O
"37"File access denied (permissions)OPEN
"39"File attribute mismatchOPEN
"41"File already openOPEN
"42"File not openCLOSE, READ, WRITE
"46"Read beyond file endREAD
"47"Input/output errorOPEN, CLOSE, READ, WRITE
"48"File not open in correct modeREAD, WRITE
"93"Resource unavailableOPEN

Comprehensive Status Checking

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
IDENTIFICATION DIVISION. PROGRAM-ID. STATUSCHK. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT DATA-FILE ASSIGN TO "DATA.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS DATA-STATUS. DATA DIVISION. FILE SECTION. FD DATA-FILE RECORD CONTAINS 100 CHARACTERS. 01 DATA-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 FILE-VARIABLES. 05 DATA-STATUS PIC XX. 88 STATUS-OK VALUE "00". 88 END-OF-FILE VALUE "10". 88 FILE-NOT-FOUND VALUE "35". 05 EOF-FLAG PIC X VALUE "N". 88 AT-END VALUE "Y". 05 ERROR-FLAG PIC X VALUE "N". 88 ERROR-OCCURRED VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZE-PROCESSING IF NOT ERROR-OCCURRED PERFORM PROCESS-DATA UNTIL AT-END OR ERROR-OCCURRED END-IF PERFORM TERMINATE-PROCESSING STOP RUN. INITIALIZE-PROCESSING. PERFORM OPEN-DATA-FILE IF ERROR-OCCURRED DISPLAY "Cannot continue processing due to file error" END-IF. PROCESS-DATA. PERFORM READ-DATA-RECORD IF NOT AT-END AND NOT ERROR-OCCURRED PERFORM PROCESS-RECORD END-IF. TERMINATE-PROCESSING. PERFORM CLOSE-DATA-FILE DISPLAY "Processing complete". OPEN-DATA-FILE. OPEN INPUT DATA-FILE PERFORM CHECK-FILE-STATUS. READ-DATA-RECORD. READ DATA-FILE AT END SET AT-END TO TRUE END-READ PERFORM CHECK-FILE-STATUS. CLOSE-DATA-FILE. CLOSE DATA-FILE PERFORM CHECK-FILE-STATUS. PROCESS-RECORD. * Process the current record DISPLAY DATA-RECORD. CHECK-FILE-STATUS. EVALUATE DATA-STATUS WHEN "00" * Operation successful - no action needed CONTINUE WHEN "10" * End of file - not an error for READ IF NOT AT-END SET AT-END TO TRUE END-IF WHEN "35" DISPLAY "File not found" SET ERROR-OCCURRED TO TRUE WHEN "37" DISPLAY "Access denied - check permissions" SET ERROR-OCCURRED TO TRUE WHEN "39" DISPLAY "Attribute mismatch - check file definition" SET ERROR-OCCURRED TO TRUE WHEN "41" DISPLAY "File already open" SET ERROR-OCCURRED TO TRUE WHEN "42" DISPLAY "File not open" SET ERROR-OCCURRED TO TRUE WHEN "46" DISPLAY "Read beyond end of file" SET ERROR-OCCURRED TO TRUE WHEN "47" DISPLAY "I/O error - check hardware" SET ERROR-OCCURRED TO TRUE WHEN "48" DISPLAY "File not open in correct mode" SET ERROR-OCCURRED TO TRUE WHEN OTHER DISPLAY "Unexpected file status: " DATA-STATUS SET ERROR-OCCURRED TO TRUE END-EVALUATE.

This example demonstrates a comprehensive approach to file status checking. A centralized CHECK-FILE-STATUS routine examines the status after each file operation and takes appropriate action based on the specific status code.

Extended File Status

Some COBOL implementations support an extended file status, which provides more detailed information about file operations. The extended status typically consists of:

  • Two-character primary status (standard file status)
  • Additional characters or fields with implementation-specific details
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO CUSTFILE FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. WORKING-STORAGE SECTION. * Standard file status 01 CUSTOMER-STATUS. 05 PRIMARY-STATUS PIC XX. 05 SECONDARY-STATUS PIC XXX. * Example usage IF PRIMARY-STATUS NOT = "00" DISPLAY "Error: " PRIMARY-STATUS "-" SECONDARY-STATUS END-IF.

The exact format of extended file status varies by compiler. Check your compiler documentation for specific details about extended status codes.

Best Practices for File Status Checking

  1. Check file status after every file operation
  2. Use 88-level condition names for commonly checked statuses
  3. Implement a centralized status checking routine
  4. Log detailed error information including operation type and file name
  5. Distinguish between expected conditions (like end-of-file) and true errors
  6. Include error recovery procedures where appropriate
  7. Close files properly even after errors
  8. Consider using extended file status for more detailed error information
  9. Document the meaning of status codes in program comments

File Status Logging 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
IDENTIFICATION DIVISION. PROGRAM-ID. FILELOG. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT DATA-FILE ASSIGN TO "DATA.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS DATA-STATUS. SELECT LOG-FILE ASSIGN TO "FILELOG.TXT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS LOG-STATUS. DATA DIVISION. FILE SECTION. FD DATA-FILE RECORD CONTAINS 100 CHARACTERS. 01 DATA-RECORD PIC X(100). FD LOG-FILE RECORD CONTAINS 80 CHARACTERS. 01 LOG-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-VARIABLES. 05 DATA-STATUS PIC XX. 05 LOG-STATUS PIC XX. 05 CURRENT-DATE-TIME. 10 CURRENT-DATE. 15 CURRENT-YEAR PIC 9(4). 15 CURRENT-MONTH PIC 9(2). 15 CURRENT-DAY PIC 9(2). 10 CURRENT-TIME. 15 CURRENT-HOUR PIC 9(2). 15 CURRENT-MINUTE PIC 9(2). 15 CURRENT-SECOND PIC 9(2). 15 CURRENT-MS PIC 9(2). 05 TIMESTAMP PIC X(19). 05 MESSAGE PIC X(60). PROCEDURE DIVISION. MAIN-PROCESS. OPEN OUTPUT LOG-FILE IF LOG-STATUS NOT = "00" DISPLAY "Could not open log file: " LOG-STATUS ELSE * Now try to work with the data file PERFORM LOG-MESSAGE "Starting file processing" OPEN INPUT DATA-FILE IF DATA-STATUS NOT = "00" PERFORM LOG-ERROR "OPEN" "DATA-FILE" DATA-STATUS ELSE PERFORM PROCESS-FILE CLOSE DATA-FILE PERFORM LOG-FILE-STATUS "CLOSE" "DATA-FILE" DATA-STATUS END-IF PERFORM LOG-MESSAGE "Processing complete" CLOSE LOG-FILE END-IF STOP RUN. PROCESS-FILE. PERFORM LOG-MESSAGE "Reading records" PERFORM UNTIL DATA-STATUS NOT = "00" READ DATA-FILE AT END EXIT PERFORM END-READ IF DATA-STATUS = "00" * Process the record CONTINUE ELSE IF DATA-STATUS NOT = "10" PERFORM LOG-ERROR "READ" "DATA-FILE" DATA-STATUS EXIT PERFORM END-IF END-PERFORM. LOG-FILE-STATUS. * Parameters: operation, file-name, status MOVE FUNCTION CURRENT-DATE TO CURRENT-DATE-TIME STRING CURRENT-YEAR "-" CURRENT-MONTH "-" CURRENT-DAY " " CURRENT-HOUR ":" CURRENT-MINUTE ":" CURRENT-SECOND INTO TIMESTAMP STRING TIMESTAMP " " FUNCTION TRIM(FUNCTION-ID-1) " " FUNCTION TRIM(FUNCTION-ID-2) " Status: " FUNCTION-ID-3 INTO MESSAGE PERFORM WRITE-LOG-RECORD. LOG-ERROR. * Parameters: operation, file-name, status MOVE FUNCTION CURRENT-DATE TO CURRENT-DATE-TIME STRING CURRENT-YEAR "-" CURRENT-MONTH "-" CURRENT-DAY " " CURRENT-HOUR ":" CURRENT-MINUTE ":" CURRENT-SECOND INTO TIMESTAMP STRING TIMESTAMP " ERROR: " FUNCTION TRIM(FUNCTION-ID-1) " " FUNCTION TRIM(FUNCTION-ID-2) " Failed with status: " FUNCTION-ID-3 INTO MESSAGE PERFORM WRITE-LOG-RECORD. LOG-MESSAGE. * Parameters: message-text MOVE FUNCTION CURRENT-DATE TO CURRENT-DATE-TIME STRING CURRENT-YEAR "-" CURRENT-MONTH "-" CURRENT-DAY " " CURRENT-HOUR ":" CURRENT-MINUTE ":" CURRENT-SECOND INTO TIMESTAMP STRING TIMESTAMP " " FUNCTION TRIM(FUNCTION-ID-1) INTO MESSAGE PERFORM WRITE-LOG-RECORD. WRITE-LOG-RECORD. MOVE MESSAGE TO LOG-RECORD WRITE LOG-RECORD IF LOG-STATUS NOT = "00" DISPLAY "Error writing to log: " LOG-STATUS END-IF.

This example demonstrates a more advanced approach with a dedicated logging system for file operations. It creates timestamped log entries for each file operation, including the operation type, file name, and status code, providing a detailed audit trail of file processing.

Test Your Knowledge

1. Which OPEN mode allows both reading and writing to an existing file?

  • INPUT
  • OUTPUT
  • I-O
  • EXTEND

2. What happens when you open a file with OUTPUT mode that already exists?

  • The file is opened for reading
  • The existing file is deleted and a new empty file is created
  • The existing contents are preserved and new records are appended
  • An error occurs and the file remains unchanged

3. What is the purpose of the AT END clause in a READ statement?

  • To specify what happens when no more records exist in the file
  • To limit the number of records read
  • To skip to the end of the file
  • To read only the last record

4. What is the correct sequence of operations for processing a sequential file?

  • OPEN, WRITE, CLOSE
  • OPEN, READ, PROCESS, CLOSE
  • READ, PROCESS, WRITE, CLOSE
  • WRITE, OPEN, PROCESS, CLOSE

5. What is the purpose of checking the file status after file operations?

  • To improve performance
  • To detect and handle errors or exceptional conditions
  • To count the number of records processed
  • To determine the file size

Frequently Asked Questions