Indexed files in COBOL use key-based access methods to store and retrieve data, allowing for both sequential and random access. The OPEN statement for indexed files is similar to sequential files but requires appropriate file declarations in the ENVIRONMENT DIVISION to specify the key fields and organization.
123456789101112131415161718192021222324252627282930313233343536ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO CUSTFILE ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-NAME WITH DUPLICATES FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 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. 05 FILLER PIC X(6). WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. PROCEDURE DIVISION. MAIN-PROCESS. OPEN I-O CUSTOMER-FILE IF CUSTOMER-STATUS = "00" PERFORM PROCESS-CUSTOMERS ELSE PERFORM FILE-ERROR-HANDLER END-IF CLOSE CUSTOMER-FILE STOP RUN.
Mode | Description | Operations Allowed |
---|---|---|
INPUT | Opens for reading only | READ, START |
OUTPUT | Creates a new file | WRITE |
I-O | Opens for reading and writing | READ, WRITE, REWRITE, DELETE, START |
EXTEND | Opens for adding records | WRITE (adding new records only) |
Access Mode | Description | Common Operations |
---|---|---|
SEQUENTIAL | Records are accessed in key sequence | READ NEXT, WRITE (in key order) |
RANDOM | Records are accessed directly by key | READ with specific key values |
DYNAMIC | Combines sequential and random access | READ NEXT and direct READ operations |
DYNAMIC is the most flexible access mode, allowing both sequential processing and direct record access as needed.
Status Code | Meaning | Typical Solution |
---|---|---|
"00" | Successful operation | Proceed with file operations |
"35" | File not found | Create file or check path/name |
"37" | Open mode not permitted | Check file permissions |
"41" | File already open | Close file before reopening |
"93" | Resource not available | Check resource allocation |
"96" | No file space in directory | Free space or use different location |
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081IDENTIFICATION DIVISION. PROGRAM-ID. INDEXCRT. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.IDX" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS CUST-ID ALTERNATE RECORD KEY IS CUST-NAME WITH DUPLICATES FILE STATUS IS FILE-STATUS. SELECT INPUT-FILE ASSIGN TO "CUSTDATA.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS INPUT-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 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. 05 FILLER PIC X(6). FD INPUT-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 100 CHARACTERS. 01 INPUT-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. 01 INPUT-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-RECORDS UNTIL END-OF-FILE 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 CUSTOMER-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error creating indexed file: " FILE-STATUS MOVE "Y" TO EOF-FLAG CLOSE INPUT-FILE END-IF END-IF. PROCESS-RECORDS. READ INPUT-FILE INTO CUSTOMER-RECORD AT END MOVE "Y" TO EOF-FLAG NOT AT END WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Duplicate or invalid key: " CUST-ID NOT INVALID KEY DISPLAY "Record written for: " CUST-ID END-WRITE END-READ. TERMINATION. CLOSE INPUT-FILE CLOSE CUSTOMER-FILE DISPLAY "File creation complete." DISPLAY "File status: " FILE-STATUS.
This example demonstrates creating an indexed file by reading data from a sequential file and writing it to a new indexed file. It includes proper error handling for both file opening and key validation.
The READ statement for indexed files has several formats, allowing for sequential access in key order or direct access using specific key values. This flexibility is one of the primary advantages of indexed files over sequential files.
123456789101112* Sequential access (next record in key sequence) READ file-name NEXT RECORD [INTO identifier-1] [AT END imperative-statement-1] [NOT AT END imperative-statement-2] [END-READ] * Random access (specific record by key) READ file-name RECORD [INTO identifier-1] KEY IS data-name-1 [INVALID KEY imperative-statement-1] [NOT INVALID KEY imperative-statement-2] [END-READ]
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455IDENTIFICATION DIVISION. PROGRAM-ID. INDEXSEQ. 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 FILE STATUS IS FILE-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 FILE-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 FILE-STATUS NOT = "00" DISPLAY "Error opening file: " FILE-STATUS MOVE "Y" TO EOF-FLAG END-IF. PROCESS-RECORDS. READ CUSTOMER-FILE NEXT RECORD AT END MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO RECORD-COUNT DISPLAY "Record " RECORD-COUNT ": " CUST-ID " - " CUST-NAME END-READ. TERMINATION. CLOSE CUSTOMER-FILE DISPLAY "Total records read: " RECORD-COUNT.
This example reads all records from an indexed file in key sequence (sorted by CUST-ID) using the READ NEXT format. This is similar to reading a sequential file, but the records are retrieved in primary key order.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081IDENTIFICATION DIVISION. PROGRAM-ID. INDEXRND. 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 ALTERNATE RECORD KEY IS CUST-NAME WITH DUPLICATES FILE STATUS IS FILE-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 FILE-STATUS PIC XX. 88 RECORD-FOUND VALUE "00". 88 RECORD-NOT-FOUND VALUE "23". 01 SEARCH-ID PIC 9(5). 01 SEARCH-NAME PIC X(30). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM UNTIL 1 = 2 DISPLAY "Enter customer ID (or 0 to quit): " ACCEPT SEARCH-ID IF SEARCH-ID = 0 EXIT PERFORM END-IF PERFORM FIND-BY-ID DISPLAY "Enter customer name (or X to quit): " ACCEPT SEARCH-NAME IF SEARCH-NAME = "X" EXIT PERFORM END-IF PERFORM FIND-BY-NAME END-PERFORM PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening file: " FILE-STATUS STOP RUN END-IF. FIND-BY-ID. MOVE SEARCH-ID TO CUST-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "No customer found with ID: " SEARCH-ID NOT INVALID KEY DISPLAY "Found: " CUST-ID " - " CUST-NAME DISPLAY "Balance: " CUST-BALANCE END-READ. FIND-BY-NAME. MOVE SEARCH-NAME TO CUST-NAME READ CUSTOMER-FILE KEY IS CUST-NAME INVALID KEY DISPLAY "No customer found with name: " SEARCH-NAME NOT INVALID KEY DISPLAY "Found: " CUST-ID " - " CUST-NAME DISPLAY "Balance: " CUST-BALANCE END-READ. TERMINATION. CLOSE CUSTOMER-FILE.
This example demonstrates direct record access using both primary and alternate keys. It allows the user to search for customers by either ID or name, demonstrating the flexibility of indexed file access.
123456789101112131415161718192021* Reading with primary key (default) MOVE 12345 TO CUST-ID READ CUSTOMER-FILE INVALID KEY PERFORM RECORD-NOT-FOUND-ROUTINE END-READ * Reading with alternate key MOVE "SMITH JOHN" TO CUST-NAME READ CUSTOMER-FILE KEY IS CUST-NAME INVALID KEY PERFORM NAME-NOT-FOUND-ROUTINE END-READ * Handling duplicate alternate keys MOVE "SMITH" TO CUST-NAME * First read gets the first occurrence READ CUSTOMER-FILE KEY IS CUST-NAME INVALID KEY PERFORM NAME-NOT-FOUND-ROUTINE END-READ * Subsequent reads need a START and READ NEXT combination * See the START section for handling duplicates
When reading with alternate keys that allow duplicates, only the first occurrence is retrieved with a direct READ. To access all records with the same alternate key value, use the START statement to position at the first occurrence, then use READ NEXT to retrieve all matching records.
Status Code | Meaning | Condition |
---|---|---|
"00" | Successful operation | Record found and read |
"10" | End of file | No more records (READ NEXT) |
"23" | Record not found | Key value not in file |
"46" | Read beyond file end | Sequential read after end |
"47" | File not open in correct mode | File not open for input |
The WRITE statement for indexed files adds records to the file based on the key values in the record. Unlike sequential files, the physical placement of the record is determined by the key values rather than the sequence of WRITE operations. This ensures that records can be retrieved efficiently using their keys.
1234WRITE record-name [FROM identifier-1] [INVALID KEY imperative-statement-1] [NOT INVALID KEY imperative-statement-2] [END-WRITE]
Aspect | Rule | Example |
---|---|---|
Primary Key | Must be unique; duplicate values cause error | CUSTOMER-ID, ISBN, ACCOUNT-NUMBER |
Alternate Keys | Can allow duplicates if specified | CUSTOMER-NAME, ZIP-CODE, PRODUCT-CATEGORY |
Key Initialization | All key fields must be properly populated | MOVE "12345" TO CUSTOMER-ID |
OPEN Mode | Requires OUTPUT, I-O, or EXTEND mode | OPEN OUTPUT CUSTOMER-FILE |
Record Order | Physical order determined by key values | Records are stored in primary key sequence |
123456789101112131415161718192021222324252627282930313233343536373839* Simple WRITE with error handling MOVE "12345" TO CUSTOMER-ID MOVE "JOHN SMITH" TO CUSTOMER-NAME MOVE "123 MAIN ST" TO CUSTOMER-ADDRESS MOVE 1000.00 TO CUSTOMER-BALANCE WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error writing record: " CUSTOMER-ID PERFORM ERROR-ROUTINE NOT INVALID KEY DISPLAY "Record written successfully" END-WRITE * WRITE with FROM clause MOVE "12345" TO WS-CUSTOMER-ID MOVE "JOHN SMITH" TO WS-CUSTOMER-NAME MOVE "123 MAIN ST" TO WS-CUSTOMER-ADDRESS MOVE 1000.00 TO WS-CUSTOMER-BALANCE WRITE CUSTOMER-RECORD FROM WORK-CUSTOMER-RECORD INVALID KEY DISPLAY "Error writing record: " WS-CUSTOMER-ID END-WRITE * Status checking approach MOVE "12345" TO CUSTOMER-ID MOVE "JOHN SMITH" TO CUSTOMER-NAME MOVE "123 MAIN ST" TO CUSTOMER-ADDRESS MOVE 1000.00 TO CUSTOMER-BALANCE WRITE CUSTOMER-RECORD IF FILE-STATUS = "00" DISPLAY "Record written successfully" ELSE IF FILE-STATUS = "22" DISPLAY "Duplicate key: " CUSTOMER-ID ELSE DISPLAY "Error writing record: " FILE-STATUS END-IF
These examples demonstrate different approaches to writing records to an indexed file, including error handling for invalid key conditions. The FROM clause is useful when working with multiple record formats or when you need to preserve the original record.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293IDENTIFICATION DIVISION. PROGRAM-ID. INDEXADD. 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 ALTERNATE RECORD KEY IS CUST-NAME WITH DUPLICATES FILE STATUS IS FILE-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 FILE-STATUS PIC XX. 88 SUCCESS VALUE "00". 88 DUPLICATE-KEY VALUE "22". 01 WORK-FIELDS. 05 MORE-RECORDS PIC X VALUE "Y". 88 NO-MORE-RECORDS VALUE "N". 05 KEY-EXISTS PIC X. 88 KEY-ALREADY-EXISTS VALUE "Y". 88 KEY-IS-NEW VALUE "N". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM ADD-RECORDS UNTIL NO-MORE-RECORDS PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN I-O CUSTOMER-FILE IF NOT SUCCESS DISPLAY "File does not exist, creating new file" CLOSE CUSTOMER-FILE OPEN OUTPUT CUSTOMER-FILE IF NOT SUCCESS DISPLAY "Could not create file: " FILE-STATUS MOVE "N" TO MORE-RECORDS END-IF END-IF. ADD-RECORDS. INITIALIZE CUSTOMER-RECORD DISPLAY "Enter customer ID (or 0 to quit): " ACCEPT CUST-ID IF CUST-ID = 0 MOVE "N" TO MORE-RECORDS ELSE PERFORM CHECK-IF-KEY-EXISTS IF NOT KEY-ALREADY-EXISTS DISPLAY "Enter customer name: " ACCEPT CUST-NAME DISPLAY "Enter customer address: " ACCEPT CUST-ADDRESS DISPLAY "Enter customer balance: " ACCEPT CUST-BALANCE WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error writing record - status: " FILE-STATUS NOT INVALID KEY DISPLAY "Record added successfully" END-WRITE END-IF END-IF. CHECK-IF-KEY-EXISTS. MOVE "N" TO KEY-EXISTS READ CUSTOMER-FILE INVALID KEY CONTINUE NOT INVALID KEY DISPLAY "Customer ID " CUST-ID " already exists" DISPLAY "Name: " CUST-NAME MOVE "Y" TO KEY-EXISTS END-READ. TERMINATION. CLOSE CUSTOMER-FILE.
This example demonstrates a complete program for adding records to an indexed file, with proper error handling and validation. It includes checking for duplicate keys before attempting to write, which provides better user feedback.
Status Code | Meaning | Handling Approach |
---|---|---|
"00" | Successful operation | Continue processing |
"22" | Duplicate key | Generate new key or update existing record |
"24" | Boundary violation | Check record size against file definition |
"34" | Disk full or space allocation exceeded | Free disk space or extend allocation |
"48" | File not open in write mode | Check OPEN mode (needs OUTPUT, I-O, or EXTEND) |
Status code "22" (duplicate key) is particularly important for indexed files and should always be handled explicitly when writing records.
The START statement positions the file pointer at a record with a specific key value or key condition. This is essential for accessing indexed files in a specific sequence or for finding groups of records that match certain criteria. After positioning with START, subsequent READ NEXT operations retrieve records starting from that position.
123456789101112START file-name KEY {IS EQUAL TO | IS = | IS GREATER THAN | IS > | IS NOT LESS THAN| IS NOT < | IS GREATER THAN OR EQUAL TO | IS >= } data-name-1 [INVALID KEY imperative-statement-1] [NOT INVALID KEY imperative-statement-2] [END-START]
Operation | Description | Usage |
---|---|---|
EQUAL TO (=) | Exact match only | Finding specific records |
GREATER THAN (>) | First record with key > value | Processing ranges above a threshold |
NOT LESS THAN (NOT <) | First record with key >= value | Processing inclusive ranges |
GREATER THAN OR EQUAL TO (>=) | First record with key >= value | Same as NOT LESS THAN |
If no KEY clause is specified, the default is EQUAL TO for the primary key. These comparison operators determine which record the file pointer is positioned at for subsequent READ NEXT operations.
123456789101112131415161718192021222324252627282930313233343536373839* Position at an exact customer ID MOVE "12345" TO CUSTOMER-ID START CUSTOMER-FILE KEY IS = CUSTOMER-ID INVALID KEY DISPLAY "Customer " CUSTOMER-ID " not found" NOT INVALID KEY PERFORM READ-CUSTOMER-RECORD END-START * Position at customers with IDs >= 50000 MOVE "50000" TO CUSTOMER-ID START CUSTOMER-FILE KEY IS NOT < CUSTOMER-ID INVALID KEY DISPLAY "No customers with ID >= 50000" NOT INVALID KEY PERFORM PROCESS-CUSTOMERS UNTIL END-OF-FILE END-START * Position at customers in a specific ZIP code MOVE "90210" TO CUSTOMER-ZIP START CUSTOMER-FILE KEY IS = CUSTOMER-ZIP INVALID KEY DISPLAY "No customers in ZIP code " CUSTOMER-ZIP NOT INVALID KEY PERFORM PROCESS-ZIP-CUSTOMERS UNTIL NO-MORE-IN-ZIP END-START * Example of reading duplicate alternate keys PROCESS-ZIP-CUSTOMERS. READ CUSTOMER-FILE NEXT RECORD AT END SET END-OF-FILE TO TRUE NOT AT END IF CUSTOMER-ZIP NOT = "90210" SET NO-MORE-IN-ZIP TO TRUE ELSE DISPLAY CUSTOMER-NAME " lives in Beverly Hills" END-IF END-READ.
These examples demonstrate how START positions the file for subsequent READ NEXT operations. This combination is particularly useful for processing ranges of records or records with duplicate alternate keys.
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192IDENTIFICATION DIVISION. PROGRAM-ID. DATERANGE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT TRANSACTION-FILE ASSIGN TO "TRANSACT.IDX" ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS TRANS-ID ALTERNATE RECORD KEY IS TRANS-DATE FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD TRANSACTION-FILE LABEL RECORDS ARE STANDARD. 01 TRANSACTION-RECORD. 05 TRANS-ID PIC 9(8). 05 TRANS-DATE PIC 9(8). * YYYYMMDD 05 TRANS-AMOUNT PIC S9(7)V99. 05 TRANS-TYPE PIC X. 88 DEPOSIT VALUE "D". 88 WITHDRAWAL VALUE "W". 05 TRANS-ACCOUNT PIC 9(10). 05 TRANS-DESCRIPTION PIC X(50). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. 01 START-DATE PIC 9(8). 01 END-DATE PIC 9(8). 01 TOTAL-AMOUNT PIC S9(9)V99 VALUE ZERO. 01 TRANS-COUNT PIC 9(5) VALUE ZERO. 01 FLAGS. 05 EOF-FLAG PIC X VALUE "N". 88 END-OF-FILE VALUE "Y". 05 RANGE-FLAG PIC X VALUE "N". 88 END-OF-RANGE VALUE "Y". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-DATE-RANGE PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN INPUT TRANSACTION-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening file: " FILE-STATUS MOVE "Y" TO EOF-FLAG ELSE DISPLAY "Enter start date (YYYYMMDD): " ACCEPT START-DATE DISPLAY "Enter end date (YYYYMMDD): " ACCEPT END-DATE END-IF. PROCESS-DATE-RANGE. MOVE START-DATE TO TRANS-DATE START TRANSACTION-FILE KEY IS NOT < TRANS-DATE INVALID KEY DISPLAY "No transactions on or after " START-DATE MOVE "Y" TO EOF-FLAG END-START PERFORM UNTIL END-OF-FILE OR END-OF-RANGE READ TRANSACTION-FILE NEXT RECORD AT END MOVE "Y" TO EOF-FLAG NOT AT END IF TRANS-DATE > END-DATE MOVE "Y" TO RANGE-FLAG ELSE ADD 1 TO TRANS-COUNT IF DEPOSIT ADD TRANS-AMOUNT TO TOTAL-AMOUNT ELSE SUBTRACT TRANS-AMOUNT FROM TOTAL-AMOUNT END-IF DISPLAY "Transaction on " TRANS-DATE ": " TRANS-AMOUNT " (" TRANS-TYPE ")" END-IF END-READ END-PERFORM. TERMINATION. CLOSE TRANSACTION-FILE DISPLAY "Transactions processed: " TRANS-COUNT DISPLAY "Net amount: " TOTAL-AMOUNT.
This example uses START with the NOT LESS THAN operation to position at the beginning of a date range, then reads sequentially until the end date is exceeded. This demonstrates a common pattern for processing time-based data in indexed files.
123456789101112131415161718192021* Using the primary key MOVE "12345" TO CUSTOMER-ID START CUSTOMER-FILE KEY IS = CUSTOMER-ID ... * Using an alternate key MOVE "SMITH" TO CUSTOMER-NAME START CUSTOMER-FILE KEY IS = CUSTOMER-NAME ... * Finding partial key matches (prefix search) MOVE "SMITH" TO CUSTOMER-NAME MOVE SPACES TO CUSTOMER-NAME(6:25) * Clear the rest of the field START CUSTOMER-FILE KEY IS NOT < CUSTOMER-NAME ... * Then read until no longer matching the prefix READ CUSTOMER-FILE NEXT RECORD ... IF CUSTOMER-NAME(1:5) NOT = "SMITH" * No longer in the SMITH records ...
These examples show how to use START with different key fields. The last example demonstrates a technique for prefix searching, which is useful for finding all records that begin with certain characters.
Status Code | Meaning | Handling Approach |
---|---|---|
"00" | Successful operation | Proceed with READ NEXT operations |
"23" | Record not found | No matching key; handle as end of processing |
"46" | Read beyond file end | Key value exceeds highest in file |
"47" | File not open in input mode | Check OPEN mode (needs INPUT or I-O) |
The DELETE and REWRITE statements allow you to modify existing records in indexed files. DELETE removes a record from the file, while REWRITE updates an existing record. Both operations rely on proper record identification using key values.
1234DELETE file-name RECORD [INVALID KEY imperative-statement-1] [NOT INVALID KEY imperative-statement-2] [END-DELETE]
1234REWRITE record-name [FROM identifier-1] [INVALID KEY imperative-statement-1] [NOT INVALID KEY imperative-statement-2] [END-REWRITE]
12345678910111213141516171819202122232425262728293031* DELETE example * First read the record MOVE "12345" TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " CUSTOMER-ID " not found" NOT INVALID KEY DELETE CUSTOMER-FILE RECORD INVALID KEY DISPLAY "Error deleting customer " CUSTOMER-ID NOT INVALID KEY DISPLAY "Customer " CUSTOMER-ID " deleted" END-DELETE END-READ * REWRITE example * First read the record MOVE "12345" TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " CUSTOMER-ID " not found" NOT INVALID KEY * Modify fields (except primary key) MOVE "NEW ADDRESS" TO CUSTOMER-ADDRESS REWRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error updating customer " CUSTOMER-ID NOT INVALID KEY DISPLAY "Customer " CUSTOMER-ID " updated" END-REWRITE END-READ
These examples demonstrate the basic pattern for DELETE and REWRITE operations: first read the record to establish currency, then perform the operation with appropriate error handling.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129IDENTIFICATION DIVISION. PROGRAM-ID. RECMAINT. 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 FILE-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 FILE-STATUS PIC XX. 88 SUCCESS VALUE "00". 88 RECORD-NOT-FOUND VALUE "23". 01 MENU-CHOICE PIC 9. 01 SEARCH-ID PIC 9(5). 01 CONTINUE-FLAG PIC X VALUE "Y". 88 EXIT-PROGRAM VALUE "N". PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM UNTIL EXIT-PROGRAM PERFORM DISPLAY-MENU EVALUATE MENU-CHOICE WHEN 1 PERFORM UPDATE-CUSTOMER WHEN 2 PERFORM DELETE-CUSTOMER WHEN 3 MOVE "N" TO CONTINUE-FLAG WHEN OTHER DISPLAY "Invalid choice" END-EVALUATE END-PERFORM PERFORM TERMINATION STOP RUN. INITIALIZATION. OPEN I-O CUSTOMER-FILE IF NOT SUCCESS DISPLAY "Error opening file: " FILE-STATUS MOVE "N" TO CONTINUE-FLAG END-IF. DISPLAY-MENU. DISPLAY "CUSTOMER MAINTENANCE" DISPLAY "1. Update Customer" DISPLAY "2. Delete Customer" DISPLAY "3. Exit" DISPLAY "Enter choice: " ACCEPT MENU-CHOICE. UPDATE-CUSTOMER. DISPLAY "Enter customer ID to update: " ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUST-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " SEARCH-ID " not found" NOT INVALID KEY DISPLAY "Current information:" DISPLAY " Name: " CUST-NAME DISPLAY " Address: " CUST-ADDRESS DISPLAY " Balance: " CUST-BALANCE DISPLAY "Enter new name (or ENTER to keep current): " ACCEPT CUST-NAME DISPLAY "Enter new address (or ENTER to keep current): " ACCEPT CUST-ADDRESS DISPLAY "Enter new balance (or ENTER to keep current): " ACCEPT CUST-BALANCE REWRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error updating customer: " FILE-STATUS NOT INVALID KEY DISPLAY "Customer information updated" END-REWRITE END-READ. DELETE-CUSTOMER. DISPLAY "Enter customer ID to delete: " ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUST-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " SEARCH-ID " not found" NOT INVALID KEY DISPLAY "Customer information:" DISPLAY " Name: " CUST-NAME DISPLAY " Address: " CUST-ADDRESS DISPLAY " Balance: " CUST-BALANCE DISPLAY "Are you sure you want to delete this customer? (Y/N): " ACCEPT CONTINUE-FLAG IF CONTINUE-FLAG = "Y" DELETE CUSTOMER-FILE RECORD INVALID KEY DISPLAY "Error deleting customer: " FILE-STATUS NOT INVALID KEY DISPLAY "Customer " SEARCH-ID " deleted" END-DELETE ELSE DISPLAY "Deletion cancelled" END-IF END-READ. TERMINATION. CLOSE CUSTOMER-FILE.
This comprehensive example demonstrates a maintenance program that allows updating and deleting customer records. It includes user confirmation for deletions and demonstrates the proper sequence of operations for both REWRITE and DELETE.
When using REWRITE with indexed files, key constraints must be observed:
Key Type | Can Be Changed? | Notes |
---|---|---|
Primary Key | No | To change primary key, DELETE old record and WRITE new one |
Alternate Key (Unique) | Yes | Cannot conflict with existing values |
Alternate Key (Duplicates) | Yes | Can match existing values |
Attempting to change the primary key during REWRITE will result in an error. Changing an alternate key to a value that already exists will fail unless the WITH DUPLICATES phrase was specified for that key.
1234567891011121314151617181920212223242526272829303132333435* Process to change a primary key (ID change) * 1. Read the old record MOVE "12345" TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " CUSTOMER-ID " not found" NOT INVALID KEY * 2. Save the record data MOVE CUSTOMER-RECORD TO WORK-RECORD * 3. Delete the old record DELETE CUSTOMER-FILE RECORD INVALID KEY DISPLAY "Error deleting old record" NOT INVALID KEY * 4. Change the key in the work record MOVE "54321" TO WORK-ID * 5. Write as a new record MOVE WORK-RECORD TO CUSTOMER-RECORD WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Error writing new record" * Recovery - try to restore the old record MOVE "12345" TO CUSTOMER-ID MOVE WORK-RECORD TO CUSTOMER-RECORD WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "CRITICAL ERROR: Lost original record" END-WRITE NOT INVALID KEY DISPLAY "ID changed from 12345 to 54321" END-WRITE END-DELETE END-READ
This example demonstrates the process for changing a primary key, which requires deleting the old record and writing a new one with the updated key. Note the error recovery logic that attempts to restore the original record if the new record cannot be written.
Status Code | Meaning | Applies To |
---|---|---|
"00" | Successful operation | DELETE, REWRITE |
"22" | Duplicate key | REWRITE (alternate key conflict) |
"23" | Record not found | DELETE, REWRITE |
"43" | Record not read before DELETE/REWRITE | DELETE, REWRITE |
"47" | File not open in I-O mode | DELETE, REWRITE |
"92" | Record locked | DELETE, REWRITE (multi-user) |
1. What is the primary advantage of using indexed files over sequential files in COBOL?
2. In COBOL, which clause in the SELECT statement defines the primary key for an indexed file?
3. What happens if you attempt to WRITE a record with a key value that already exists in an indexed file?
4. Which statement is used to position the file pointer at a specific location in an indexed file before reading?
5. What is the purpose of the ALTERNATE RECORD KEY clause in indexed file declarations?
Understanding different file organizations in COBOL.
Learn about describing file structures in the DATA DIVISION.
Working with sequential files in COBOL.
Configuring file access in the ENVIRONMENT DIVISION.
Comprehensive approach to file errors.