BudiBadu Logo
Samplebadu

COBOL by Example: File Status

COBOL 2002

Implementing robust error handling with FILE STATUS codes for I/O operations, checking two-digit status values after file commands, understanding common codes like 00 for success and 10 for EOF, and gracefully handling errors.

Code

       IDENTIFICATION DIVISION.
       PROGRAM-ID. STATUS-DEMO.
       
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT MY-FILE ASSIGN TO "test.dat"
           FILE STATUS IS FS-CODE.
           
       DATA DIVISION.
       FILE SECTION.
       FD  MY-FILE.
       01  MY-REC PIC X(10).
       
       WORKING-STORAGE SECTION.
       01  FS-CODE PIC 99.
       
       PROCEDURE DIVISION.
           OPEN INPUT MY-FILE.
           IF FS-CODE NOT = "00"
               DISPLAY "Error opening file. Status: " FS-CODE
               STOP RUN
           END-IF.
           
           READ MY-FILE.
           IF FS-CODE = "10"
               DISPLAY "End of file reached immediately."
           END-IF.
           
           CLOSE MY-FILE.
           STOP RUN.

Explanation

Relying solely on AT END or INVALID KEY is not enough for robust applications. COBOL provides FILE STATUS codes to give detailed feedback on every I/O operation. By defining a 2-digit variable and linking it with FILE STATUS IS..., the system will populate it after every file operation.

Checking the file status variable after every I/O command is a best practice in production COBOL programming. It allows you to handle specific errors gracefully, such as creating a missing file if status 35 is returned, or retrying a locked record.

Understanding these codes is essential for debugging. For instance, a status of "9x" usually indicates a system-specific error that might require looking at system logs, whereas "2x" indicates an invalid key in an indexed file.

Common Status Codes:

  • 00: Success.
  • 10: End of File.
  • 23: Record not found (Indexed/Relative).
  • 35: File not found (on OPEN).
  • 37: Permission denied.

Code Breakdown

7
FILE STATUS IS FS-CODE. Tells the system to store the result code of any operation on MY-FILE into the variable FS-CODE.
14
01 FS-CODE PIC 99. The variable to hold the 2-digit status code. It must be a 2-character alphanumeric or numeric field.
18
IF FS-CODE NOT = "00". Checks if the OPEN command failed. "00" is the universal success code.
23
READ MY-FILE. Attempts to read a record. This will update FS-CODE.
24
IF FS-CODE = "10". Code "10" specifically means End-Of-File. This is how we check for EOF when not using the AT END clause.