Sequential files are the simplest and most fundamental file organization in COBOL. As the name suggests, records in a sequential file are stored and accessed in sequence, one after another, from beginning to end. This organization closely mirrors the historical tape-based storage systems where COBOL originated.
Sequential files are defined in the ENVIRONMENT DIVISION using the ORGANIZATION IS SEQUENTIAL clause (or by omitting the ORGANIZATION clause, as SEQUENTIAL is the default).
1234567ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO CUSTFILE ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-FILE-STATUS.
For sequential files, the ACCESS MODE IS SEQUENTIAL clause is the only valid option. The FILE STATUS clause is optional but recommended for error handling.
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586IDENTIFICATION DIVISION. PROGRAM-ID. SEQFILE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMERS.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUST-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 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC S9(7)V99. FD REPORT-FILE. 01 REPORT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUS. 05 CUST-FILE-STATUS PIC XX. 05 REPORT-FILE-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 RECORD-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 OPEN OUTPUT REPORT-FILE IF CUST-FILE-STATUS NOT = "00" DISPLAY "Error opening customer file: " CUST-FILE-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 RECORD-COUNT PERFORM PROCESS-CUSTOMER-RECORD END-READ. PROCESS-CUSTOMER-RECORD. * Process each record sequentially MOVE SPACES TO REPORT-RECORD STRING "Customer: " DELIMITED BY SIZE CUSTOMER-ID DELIMITED BY SIZE " - " DELIMITED BY SIZE CUSTOMER-NAME DELIMITED BY SIZE " - Balance: $" DELIMITED BY SIZE CUSTOMER-BALANCE DELIMITED BY SIZE INTO REPORT-RECORD END-STRING WRITE REPORT-RECORD. FINALIZATION. CLOSE CUSTOMER-FILE MOVE SPACES TO REPORT-RECORD STRING "Total records processed: " DELIMITED BY SIZE RECORD-COUNT DELIMITED BY SIZE INTO REPORT-RECORD END-STRING WRITE REPORT-RECORD CLOSE REPORT-FILE.
This example demonstrates a typical sequential file processing pattern: open the file, read records sequentially until the end of file, process each record, and close the file. The AT END clause detects when all records have been read.
Indexed files, typically implemented as VSAM Key Sequenced Data Sets (KSDS) in mainframe environments, are a powerful file organization that combines the advantages of sequential access with the ability to directly access individual records using keys. These files maintain indexes that allow COBOL programs to quickly locate specific records without reading through the entire file.
Indexed files are defined using the ORGANIZATION IS INDEXED clause, along with a RECORD KEY clause to specify the primary key. Additional ALTERNATE RECORD KEY clauses can define secondary access paths.
123456789ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO CUSTVSAM ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-NAME WITH DUPLICATES FILE STATUS IS CUSTOMER-FILE-STATUS.
For indexed files, you can choose from three access modes:
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180IDENTIFICATION DIVISION. PROGRAM-ID. IDXFILE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTVSAM" ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-NAME WITH DUPLICATES FILE STATUS IS CUST-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 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC S9(7)V99. WORKING-STORAGE SECTION. 01 WORKING-VARIABLES. 05 CUST-FILE-STATUS PIC XX. 05 OPERATION-FLAG PIC X. 88 EXIT-PROGRAM VALUE 'X'. 05 MENU-OPTION PIC 9. 05 SEARCH-ID PIC 9(5). 05 NEW-BALANCE PIC S9(7)V99. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM UNTIL EXIT-PROGRAM DISPLAY "CUSTOMER FILE OPERATIONS" DISPLAY "1. Add Customer" DISPLAY "2. Find Customer by ID" DISPLAY "3. List All Customers" DISPLAY "4. Update Customer Balance" DISPLAY "5. Delete Customer" DISPLAY "X. Exit" DISPLAY "Enter option: " WITH NO ADVANCING ACCEPT OPERATION-FLAG EVALUATE OPERATION-FLAG WHEN '1' PERFORM ADD-CUSTOMER WHEN '2' PERFORM FIND-CUSTOMER-BY-ID WHEN '3' PERFORM LIST-ALL-CUSTOMERS WHEN '4' PERFORM UPDATE-CUSTOMER WHEN '5' PERFORM DELETE-CUSTOMER WHEN 'X' OR 'x' SET EXIT-PROGRAM TO TRUE WHEN OTHER DISPLAY "Invalid option" END-EVALUATE END-PERFORM PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN I-O CUSTOMER-FILE IF CUST-FILE-STATUS = "35" DISPLAY "Customer file does not exist. Creating new file." CLOSE CUSTOMER-FILE OPEN OUTPUT CUSTOMER-FILE CLOSE CUSTOMER-FILE OPEN I-O CUSTOMER-FILE END-IF IF CUST-FILE-STATUS NOT = "00" DISPLAY "Error opening customer file: " CUST-FILE-STATUS SET EXIT-PROGRAM TO TRUE END-IF. ADD-CUSTOMER. MOVE SPACES TO CUSTOMER-RECORD DISPLAY "Enter Customer ID: " WITH NO ADVANCING ACCEPT CUSTOMER-ID DISPLAY "Enter Customer Name: " WITH NO ADVANCING ACCEPT CUSTOMER-NAME DISPLAY "Enter Customer Address: " WITH NO ADVANCING ACCEPT CUSTOMER-ADDRESS DISPLAY "Enter Customer Balance: " WITH NO ADVANCING ACCEPT CUSTOMER-BALANCE WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error: Customer ID already exists." NOT INVALID KEY DISPLAY "Customer added successfully." END-WRITE. FIND-CUSTOMER-BY-ID. DISPLAY "Enter Customer ID to find: " WITH NO ADVANCING ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE KEY IS CUSTOMER-ID INVALID KEY DISPLAY "Customer not found." NOT INVALID KEY DISPLAY "Customer ID: " CUSTOMER-ID DISPLAY "Customer Name: " CUSTOMER-NAME DISPLAY "Customer Address: " CUSTOMER-ADDRESS DISPLAY "Customer Balance: " CUSTOMER-BALANCE END-READ. LIST-ALL-CUSTOMERS. MOVE LOW-VALUES TO CUSTOMER-ID START CUSTOMER-FILE KEY >= CUSTOMER-ID INVALID KEY DISPLAY "No records in file." NOT INVALID KEY PERFORM READ-NEXT-RECORD END-START. READ-NEXT-RECORD. READ CUSTOMER-FILE NEXT AT END DISPLAY "End of file reached." NOT AT END DISPLAY CUSTOMER-ID ": " CUSTOMER-NAME " - Balance: $" CUSTOMER-BALANCE PERFORM READ-NEXT-RECORD END-READ. UPDATE-CUSTOMER. DISPLAY "Enter Customer ID to update: " WITH NO ADVANCING ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found." NOT INVALID KEY DISPLAY "Current balance: $" CUSTOMER-BALANCE DISPLAY "Enter new balance: $" WITH NO ADVANCING ACCEPT NEW-BALANCE MOVE NEW-BALANCE TO CUSTOMER-BALANCE REWRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error updating customer." NOT INVALID KEY DISPLAY "Customer updated successfully." END-REWRITE END-READ. DELETE-CUSTOMER. DISPLAY "Enter Customer ID to delete: " WITH NO ADVANCING ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID DELETE CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found." NOT INVALID KEY DISPLAY "Customer deleted successfully." END-DELETE. FINALIZATION. CLOSE CUSTOMER-FILE.
This example demonstrates a comprehensive indexed file application that allows adding, finding, listing, updating, and deleting records. It showcases both random access (by key) and sequential access (when listing all records).
Relative files, implemented as VSAM Relative Record Data Sets (RRDS) in mainframe environments, are a file organization where records are identified by their relative position within the file, similar to an array. Each record is assigned a unique relative record number that corresponds to its location, allowing for both direct access by position and sequential processing.
Relative files are defined using the ORGANIZATION IS RELATIVE clause, along with a RELATIVE KEY clause to specify the data field that will hold the relative record number for access.
12345678ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PRODUCT-FILE ASSIGN TO PRODRRDS ORGANIZATION IS RELATIVE ACCESS MODE IS DYNAMIC RELATIVE KEY IS PRODUCT-NUMBER FILE STATUS IS PRODUCT-FILE-STATUS.
Like indexed files, relative files support three access modes:
Line sequential files are a specialized file organization primarily used in UNIX, Linux, and Windows environments. Unlike traditional sequential files, line sequential files store records with explicit line terminators (such as carriage return and/or line feed characters). This format makes them compatible with standard text editors and non-COBOL applications.
Line sequential files are defined using the ORGANIZATION IS LINE SEQUENTIAL clause. This is only available in COBOL implementations for UNIX/Linux and Windows systems.
123456ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT LOG-FILE ASSIGN TO "APPLOG.TXT" ORGANIZATION IS LINE SEQUENTIAL FILE STATUS IS LOG-FILE-STATUS.
Line sequential files only support sequential access mode. They are typically used for log files, reports, and data exchange with other applications.
Selecting the appropriate file organization for your COBOL application is a critical design decision that affects performance, maintenance, and flexibility. This choice should be based on a careful analysis of your application's requirements and access patterns.
Factor | Consideration | Recommended Organization |
---|---|---|
Access Pattern | Sequential processing of entire file | Sequential |
Access Pattern | Random access by business key | Indexed (VSAM KSDS) |
Access Pattern | Random access by position | Relative (VSAM RRDS) |
Update Frequency | Frequent updates to existing records | Indexed or Relative |
Update Frequency | Append-only operations | Sequential |
File Size | Large files with frequent random access | Indexed (with appropriate buffer size) |
Record Identification | Natural business key exists | Indexed |
Record Identification | Records naturally identified by position | Relative |
External Compatibility | Needs to be read by text editors | Line Sequential |
Feature | Sequential | Indexed | Relative | Line Sequential |
---|---|---|---|---|
Random Access | No | Yes (by key) | Yes (by position) | No |
Update in Place | No | Yes | Yes | No |
Storage Overhead | Low | High | Medium | Medium |
Processing Overhead | Low | High | Medium | Low |
Multiple Access Paths | No | Yes (alternate keys) | No | No |
Typical Use Case | Batch processing, logs | Interactive applications | Array-like storage | Text files, data exchange |
1. Which file organization type uses record keys to access data directly?
2. What is the main characteristic of sequential file organization?
3. Which COBOL file organization is best suited for applications requiring frequent inserts, updates, and random access?
4. How are records accessed in a relative file organization (VSAM RRDS)?
5. Which file organization would be most appropriate for a log file that only has new records appended to the end?
Learn about describing file structures in the DATA DIVISION.
Understanding how to work with sequential files in COBOL.
Learn about operations specific to indexed files.
How to handle file-related errors in COBOL.
Understanding how files are connected to external resources.