Indexed files in COBOL provide efficient data access through the use of indexes that map key values to record locations. This file organization allows both sequential and random access patterns, making it ideal for applications requiring fast key-based record retrieval. Understanding indexed file concepts is essential for building high-performance COBOL applications that need efficient data access and management.
Indexed files in COBOL use indexes to provide efficient access to records based on key values. The index contains key values and their corresponding record locations, allowing fast random access and maintaining sorted order. Indexed files support primary keys for unique identification and alternate keys for additional access paths. This organization provides excellent performance for both sequential and random access patterns.
Indexed files are defined using the INDEXED clause in the SELECT statement, with primary and alternate keys specified in the record description. This structure provides the foundation for efficient key-based access.
123456789101112131415161718192021222324252627282930313233343536373839IDENTIFICATION DIVISION. PROGRAM-ID. INDEXED-FILE-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO 'CUSTOMER.DAT' ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-NAME WITH DUPLICATES FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(20). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC 9(8)V99. 05 CUSTOMER-PHONE PIC X(12). WORKING-STORAGE SECTION. 01 FILE-CONTROLS. 05 FILE-STATUS PIC XX VALUE '00'. 88 FILE-OK VALUE '00'. 88 FILE-EOF VALUE '10'. 88 RECORD-FOUND VALUE '00'. 88 RECORD-NOT-FOUND VALUE '23'. PROCEDURE DIVISION. MAIN-PROGRAM. DISPLAY 'Indexed File Example' PERFORM OPEN-FILE PERFORM DEMONSTRATE-ACCESS-METHODS PERFORM CLOSE-FILE STOP RUN.
Indexed files are defined with ORGANIZATION IS INDEXED and specify primary and alternate keys. The ACCESS MODE determines how the file can be accessed, and DUPLICATES allows multiple records with the same alternate key.
Key definition involves specifying primary keys for unique record identification and alternate keys for additional access paths. Proper key design is crucial for optimal performance and data integrity.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(6). *> Primary key 05 EMPLOYEE-NAME. 10 FIRST-NAME PIC X(15). 10 LAST-NAME PIC X(20). 05 EMPLOYEE-DATA. 10 DEPARTMENT PIC X(10). *> Alternate key 10 SALARY PIC 9(8)V99. 10 HIRE-DATE PIC 9(8). 05 EMPLOYEE-ADDRESS. 10 STREET PIC X(30). 10 CITY PIC X(20). 10 STATE PIC X(2). 10 ZIP-CODE PIC X(10). WORKING-STORAGE SECTION. 01 KEY-MANAGEMENT. 05 PRIMARY-KEY PIC 9(6). 05 ALTERNATE-KEY PIC X(10). 05 KEY-STATUS PIC X(1). 88 KEY-VALID VALUE 'V'. 88 KEY-INVALID VALUE 'I'. PROCEDURE DIVISION. KEY-OPERATIONS. DISPLAY 'Managing indexed file keys' *> Set primary key for random access MOVE 123456 TO PRIMARY-KEY PERFORM ACCESS-BY-PRIMARY-KEY *> Set alternate key for department search MOVE 'SALES' TO ALTERNATE-KEY PERFORM ACCESS-BY-ALTERNATE-KEY. ACCESS-BY-PRIMARY-KEY. MOVE PRIMARY-KEY TO EMPLOYEE-ID READ EMPLOYEE-FILE IF RECORD-FOUND DISPLAY 'Found employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME ELSE DISPLAY 'Employee not found: ' EMPLOYEE-ID END-IF.
Key management involves using primary keys for unique record access and alternate keys for additional search criteria. Proper key usage ensures efficient data retrieval and maintains data integrity.
Sequential access reads records in key order, providing efficient processing when all records need to be processed in sorted sequence. This method is ideal for batch processing and report generation.
1234567891011121314151617181920212223PROCEDURE DIVISION. SEQUENTIAL-ACCESS. DISPLAY 'Sequential access to indexed file' OPEN INPUT EMPLOYEE-FILE *> Read records in key order PERFORM UNTIL FILE-EOF READ EMPLOYEE-FILE NEXT IF FILE-OK PERFORM PROCESS-EMPLOYEE-RECORD END-IF END-PERFORM CLOSE EMPLOYEE-FILE. PROCESS-EMPLOYEE-RECORD. DISPLAY 'Processing employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME ADD 1 TO RECORD-COUNT *> Process employee data PERFORM CALCULATE-SALARY-STATISTICS PERFORM UPDATE-DEPARTMENT-TOTALS
Sequential access using READ NEXT processes records in key order, providing efficient batch processing capabilities. This method is optimal when all records need to be processed in sequence.
Random access allows direct retrieval of specific records using key values, providing fast access to individual records without reading the entire file.
12345678910111213141516171819202122232425262728293031PROCEDURE DIVISION. RANDOM-ACCESS. DISPLAY 'Random access to indexed file' OPEN I-O EMPLOYEE-FILE *> Access specific employee by ID MOVE 123456 TO EMPLOYEE-ID READ EMPLOYEE-FILE IF RECORD-FOUND DISPLAY 'Found employee: ' FIRST-NAME ' ' LAST-NAME PERFORM UPDATE-EMPLOYEE-SALARY ELSE DISPLAY 'Employee not found: ' EMPLOYEE-ID END-IF *> Access another employee MOVE 789012 TO EMPLOYEE-ID READ EMPLOYEE-FILE IF RECORD-FOUND DISPLAY 'Found employee: ' FIRST-NAME ' ' LAST-NAME PERFORM DISPLAY-EMPLOYEE-DETAILS ELSE DISPLAY 'Employee not found: ' EMPLOYEE-ID END-IF CLOSE EMPLOYEE-FILE. UPDATE-EMPLOYEE-SALARY. ADD 5000.00 TO SALARY REWRITE EMPLOYEE-RECORD
Random access provides direct record retrieval using key values, enabling fast updates and individual record processing without sequential file traversal.
Dynamic access combines sequential and random access capabilities, allowing programs to switch between access methods as needed. This provides maximum flexibility for complex data processing.
12345678910111213141516171819202122232425262728293031PROCEDURE DIVISION. DYNAMIC-ACCESS. DISPLAY 'Dynamic access to indexed file' OPEN I-O EMPLOYEE-FILE *> Start at specific key position MOVE 100000 TO EMPLOYEE-ID START EMPLOYEE-FILE KEY IS GREATER THAN EMPLOYEE-ID *> Read sequentially from that position PERFORM UNTIL FILE-EOF READ EMPLOYEE-FILE NEXT IF FILE-OK IF SALARY > 50000.00 PERFORM PROCESS-HIGH-SALARY-EMPLOYEE ELSE PERFORM PROCESS-STANDARD-EMPLOYEE END-IF END-IF END-PERFORM CLOSE EMPLOYEE-FILE. PROCESS-HIGH-SALARY-EMPLOYEE. DISPLAY 'High salary employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME ADD 1 TO HIGH-SALARY-COUNT. PROCESS-STANDARD-EMPLOYEE. DISPLAY 'Standard employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME ADD 1 TO STANDARD-EMPLOYEE-COUNT
Dynamic access provides flexibility by allowing programs to start at specific positions and switch between sequential and random access as needed for complex processing requirements.
Duplicate key handling manages situations where multiple records have the same key value, providing control over record ordering and access patterns.
1234567891011121314151617181920212223242526272829303132PROCEDURE DIVISION. DUPLICATE-KEY-HANDLING. DISPLAY 'Handling duplicate keys' OPEN INPUT EMPLOYEE-FILE *> Access by alternate key (department) MOVE 'SALES' TO DEPARTMENT READ EMPLOYEE-FILE IF RECORD-FOUND DISPLAY 'First sales employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME *> Read additional records with same key PERFORM UNTIL FILE-EOF READ EMPLOYEE-FILE NEXT IF FILE-OK IF DEPARTMENT = 'SALES' DISPLAY 'Sales employee: ' EMPLOYEE-ID ' ' FIRST-NAME ' ' LAST-NAME ADD 1 TO SALES-COUNT ELSE EXIT PERFORM END-IF END-IF END-PERFORM ELSE DISPLAY 'No sales employees found' END-IF CLOSE EMPLOYEE-FILE. DISPLAY-SALES-STATISTICS. DISPLAY 'Total sales employees: ' SALES-COUNT
Duplicate key handling allows multiple records with the same alternate key value. Programs can access all records with the same key using sequential reads after the initial key-based access.
Key validation ensures that key values are valid before attempting file operations, preventing errors and ensuring data integrity in indexed file operations.
123456789101112131415161718192021222324252627282930313233PROCEDURE DIVISION. KEY-VALIDATION. DISPLAY 'Validating keys before file operations' *> Validate primary key MOVE INPUT-EMPLOYEE-ID TO EMPLOYEE-ID PERFORM VALIDATE-PRIMARY-KEY IF KEY-VALID READ EMPLOYEE-FILE IF RECORD-FOUND PERFORM PROCESS-EMPLOYEE ELSE DISPLAY 'Employee not found: ' EMPLOYEE-ID END-IF ELSE DISPLAY 'Invalid employee ID: ' INPUT-EMPLOYEE-ID END-IF. VALIDATE-PRIMARY-KEY. MOVE 'V' TO KEY-STATUS *> Check for valid range IF EMPLOYEE-ID < 100000 OR EMPLOYEE-ID > 999999 DISPLAY 'ERROR: Employee ID out of range: ' EMPLOYEE-ID MOVE 'I' TO KEY-STATUS END-IF *> Check for numeric IF EMPLOYEE-ID NOT NUMERIC DISPLAY 'ERROR: Employee ID must be numeric: ' EMPLOYEE-ID MOVE 'I' TO KEY-STATUS END-IF
Key validation ensures that key values meet required criteria before file operations. This prevents errors and maintains data integrity in indexed file processing.
Index optimization involves choosing appropriate keys, minimizing index size, and optimizing access patterns to achieve optimal performance for indexed file operations.
12345678910111213141516171819202122232425262728PROCEDURE DIVISION. INDEX-OPTIMIZATION. DISPLAY 'Optimizing index performance' *> Use most selective key first PERFORM ACCESS-BY-MOST-SELECTIVE-KEY *> Minimize index updates PERFORM BATCH-UPDATE-OPERATIONS *> Use appropriate access mode PERFORM CHOOSE-OPTIMAL-ACCESS-MODE. ACCESS-BY-MOST-SELECTIVE-KEY. *> Use primary key for unique access MOVE UNIQUE-EMPLOYEE-ID TO EMPLOYEE-ID READ EMPLOYEE-FILE IF RECORD-FOUND DISPLAY 'Found unique employee: ' EMPLOYEE-ID END-IF. BATCH-UPDATE-OPERATIONS. DISPLAY 'Performing batch updates' *> Group similar operations to minimize index updates PERFORM VARYING UPDATE-INDEX FROM 1 BY 1 UNTIL UPDATE-INDEX > 10 PERFORM SINGLE-UPDATE-OPERATION END-PERFORM
Index optimization focuses on using the most selective keys, minimizing index updates, and choosing appropriate access modes to achieve optimal performance for indexed file operations.
Access pattern optimization involves choosing the most efficient access method for specific operations, minimizing I/O operations, and optimizing data retrieval patterns.
123456789101112131415161718192021222324252627PROCEDURE DIVISION. ACCESS-PATTERN-OPTIMIZATION. DISPLAY 'Optimizing access patterns' *> Use random access for individual records PERFORM RANDOM-ACCESS-FOR-SINGLE-RECORDS *> Use sequential access for batch processing PERFORM SEQUENTIAL-ACCESS-FOR-BATCH-PROCESSING *> Use dynamic access for complex queries PERFORM DYNAMIC-ACCESS-FOR-COMPLEX-QUERIES. RANDOM-ACCESS-FOR-SINGLE-RECORDS. MOVE SPECIFIC-EMPLOYEE-ID TO EMPLOYEE-ID READ EMPLOYEE-FILE IF RECORD-FOUND PERFORM PROCESS-SINGLE-EMPLOYEE END-IF. SEQUENTIAL-ACCESS-FOR-BATCH-PROCESSING. PERFORM UNTIL FILE-EOF READ EMPLOYEE-FILE NEXT IF FILE-OK PERFORM PROCESS-EMPLOYEE-FOR-BATCH END-IF END-PERFORM
Access pattern optimization involves choosing the most efficient access method for specific operations, balancing performance requirements with processing needs.