MainframeMaster

COBOL Tutorial

COBOL Access Methods

Progress0 of 0 lessons

Introduction to Access Methods

Access methods in COBOL define the techniques used to retrieve data from files, determining how records are located, read, and processed. The choice of access method significantly impacts program performance, data organization, and application functionality.

COBOL supports several access methods, each optimized for different scenarios:

  • Sequential Access: Reading records in the order they appear in the file
  • Indexed Access: Using key values to directly locate specific records
  • Relative Access: Accessing records by their relative position in the file
  • Random Access: Direct access to records using various criteria
  • Dynamic Access: Combining multiple access methods in a single program

Understanding these access methods is crucial for designing efficient, scalable COBOL applications that can handle large datasets effectively.

Sequential Access Method

Sequential access is the most basic and commonly used access method, where records are read in the order they appear in the file. This method is ideal for batch processing and when you need to process all records in a file.

Sequential Access Implementation

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
IDENTIFICATION DIVISION. PROGRAM-ID. SEQUENTIAL-ACCESS-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC S9(7)V99. WORKING-STORAGE SECTION. 01 FILE-STATUS PIC X(2). 01 RECORD-COUNT PIC 9(6) VALUE ZERO. 01 TOTAL-BALANCE PIC S9(9)V99 VALUE ZERO. 01 END-OF-FILE PIC X(1) VALUE 'N'. 01 SUMMARY-LINE. 05 FILLER PIC X(20) VALUE "Total Records: ". 05 SUMMARY-COUNT PIC ZZZ,ZZ9. 05 FILLER PIC X(20) VALUE "Total Balance: $". 05 SUMMARY-BALANCE PIC $$$,$$$,$$9.99. PROCEDURE DIVISION. PERFORM OPEN-FILE PERFORM PROCESS-SEQUENTIAL-RECORDS PERFORM DISPLAY-SUMMARY PERFORM CLOSE-FILE STOP RUN. OPEN-FILE. OPEN INPUT CUSTOMER-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening file: " FILE-STATUS STOP RUN END-IF DISPLAY "File opened successfully for sequential access". PROCESS-SEQUENTIAL-RECORDS. DISPLAY "Processing records sequentially..." PERFORM UNTIL END-OF-FILE = 'Y' READ CUSTOMER-FILE AT END MOVE 'Y' TO END-OF-FILE NOT AT END ADD 1 TO RECORD-COUNT ADD CUSTOMER-BALANCE TO TOTAL-BALANCE DISPLAY "Record " RECORD-COUNT ": " CUSTOMER-ID " - " CUSTOMER-NAME END-READ END-PERFORM. DISPLAY-SUMMARY. MOVE RECORD-COUNT TO SUMMARY-COUNT MOVE TOTAL-BALANCE TO SUMMARY-BALANCE DISPLAY " " DISPLAY "=== Sequential Processing Summary ===" DISPLAY SUMMARY-LINE. CLOSE-FILE. CLOSE CUSTOMER-FILE DISPLAY "File closed successfully".

Sequential Access Characteristics

  • Performance: Excellent for processing entire files
  • Memory Usage: Low memory requirements
  • Flexibility: Limited to forward-only processing
  • Use Cases: Batch processing, reporting, data migration
  • File Organization: Works with any file organization

Indexed Access Method

Indexed access allows direct retrieval of records using key values, making it ideal for applications that need to find specific records quickly without reading through the entire file.

Indexed Access Implementation

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
IDENTIFICATION DIVISION. PROGRAM-ID. INDEXED-ACCESS-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.IDX" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-NAME FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC S9(7)V99. WORKING-STORAGE SECTION. 01 FILE-STATUS PIC X(2). 01 SEARCH-KEY PIC X(6). 01 SEARCH-NAME PIC X(30). 01 RECORD-FOUND PIC X(1) VALUE 'N'. PROCEDURE DIVISION. PERFORM OPEN-FILE PERFORM DEMONSTRATE-INDEXED-ACCESS PERFORM CLOSE-FILE STOP RUN. OPEN-FILE. OPEN INPUT CUSTOMER-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening indexed file: " FILE-STATUS STOP RUN END-IF DISPLAY "Indexed file opened successfully". DEMONSTRATE-INDEXED-ACCESS. DISPLAY "=== Indexed Access Demonstration ===" * Access by primary key (Customer ID) DISPLAY "Enter Customer ID to search: " WITH NO ADVANCING ACCEPT SEARCH-KEY MOVE SEARCH-KEY TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer ID " SEARCH-KEY " not found" NOT INVALID KEY DISPLAY "Customer found by ID:" DISPLAY " ID: " CUSTOMER-ID DISPLAY " Name: " CUSTOMER-NAME DISPLAY " Address: " CUSTOMER-ADDRESS DISPLAY " Balance: $" CUSTOMER-BALANCE END-READ DISPLAY " " * Access by alternate key (Customer Name) DISPLAY "Enter Customer Name to search: " WITH NO ADVANCING ACCEPT SEARCH-NAME MOVE SEARCH-NAME TO CUSTOMER-NAME READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer Name " SEARCH-NAME " not found" NOT INVALID KEY DISPLAY "Customer found by Name:" DISPLAY " ID: " CUSTOMER-ID DISPLAY " Name: " CUSTOMER-NAME DISPLAY " Address: " CUSTOMER-ADDRESS DISPLAY " Balance: $" CUSTOMER-BALANCE END-READ. CLOSE-FILE. CLOSE CUSTOMER-FILE DISPLAY "Indexed file closed successfully".

Indexed Access Characteristics

  • Performance: Excellent for finding specific records
  • Memory Usage: Higher due to index maintenance
  • Flexibility: Supports multiple key access
  • Use Cases: Online transactions, lookups, updates
  • File Organization: Requires indexed organization

Relative Access Method

Relative access allows reading records by their relative position in the file, providing direct access to specific record numbers. This method is useful when you know the position of records you want to access.

Relative Access Implementation

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
IDENTIFICATION DIVISION. PROGRAM-ID. RELATIVE-ACCESS-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO "EMPLOYEE.REL" ORGANIZATION IS RELATIVE ACCESS MODE IS RANDOM RELATIVE KEY IS RECORD-NUMBER FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC X(6). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-DEPT PIC X(15). 05 EMPLOYEE-SALARY PIC S9(6)V99. WORKING-STORAGE SECTION. 01 FILE-STATUS PIC X(2). 01 RECORD-NUMBER PIC 9(6). 01 MAX-RECORDS PIC 9(6) VALUE 1000. 01 RECORD-FOUND PIC X(1). PROCEDURE DIVISION. PERFORM OPEN-FILE PERFORM DEMONSTRATE-RELATIVE-ACCESS PERFORM CLOSE-FILE STOP RUN. OPEN-FILE. OPEN INPUT EMPLOYEE-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening relative file: " FILE-STATUS STOP RUN END-IF DISPLAY "Relative file opened successfully". DEMONSTRATE-RELATIVE-ACCESS. DISPLAY "=== Relative Access Demonstration ===" * Access specific record by number DISPLAY "Enter record number to access (1-" MAX-RECORDS "): " WITH NO ADVANCING ACCEPT RECORD-NUMBER READ EMPLOYEE-FILE INVALID KEY DISPLAY "Record number " RECORD-NUMBER " not found or invalid" NOT INVALID KEY DISPLAY "Employee record found:" DISPLAY " Record #: " RECORD-NUMBER DISPLAY " ID: " EMPLOYEE-ID DISPLAY " Name: " EMPLOYEE-NAME DISPLAY " Department: " EMPLOYEE-DEPT DISPLAY " Salary: $" EMPLOYEE-SALARY END-READ DISPLAY " " * Demonstrate sequential access with relative file DISPLAY "Demonstrating sequential access on relative file..." MOVE 1 TO RECORD-NUMBER PERFORM UNTIL RECORD-NUMBER > 5 READ EMPLOYEE-FILE INVALID KEY DISPLAY "Record " RECORD-NUMBER " not found" NOT INVALID KEY DISPLAY "Record " RECORD-NUMBER ": " EMPLOYEE-NAME END-READ ADD 1 TO RECORD-NUMBER END-PERFORM. CLOSE-FILE. CLOSE EMPLOYEE-FILE DISPLAY "Relative file closed successfully".

Relative Access Characteristics

  • Performance: Good for position-based access
  • Memory Usage: Moderate memory requirements
  • Flexibility: Direct access by record number
  • Use Cases: Array-like access, fixed-size records
  • File Organization: Requires relative organization

Dynamic Access Method

Dynamic access combines multiple access methods in a single program, allowing you to switch between sequential, indexed, and relative access as needed. This provides maximum flexibility for complex applications.

Dynamic Access Implementation

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
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
IDENTIFICATION DIVISION. PROGRAM-ID. DYNAMIC-ACCESS-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PRODUCT-FILE ASSIGN TO "PRODUCT.DYN" ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS PRODUCT-ID ALTERNATE RECORD KEY IS PRODUCT-NAME RELATIVE KEY IS RECORD-POSITION FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD PRODUCT-FILE. 01 PRODUCT-RECORD. 05 PRODUCT-ID PIC X(8). 05 PRODUCT-NAME PIC X(30). 05 PRODUCT-CATEGORY PIC X(15). 05 PRODUCT-PRICE PIC S9(5)V99. 05 PRODUCT-STOCK PIC 9(5). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC X(2). 01 RECORD-POSITION PIC 9(6). 01 ACCESS-MODE PIC X(10). 01 SEARCH-KEY PIC X(30). 01 MENU-CHOICE PIC 9(1). PROCEDURE DIVISION. PERFORM OPEN-FILE PERFORM MAIN-MENU PERFORM CLOSE-FILE STOP RUN. OPEN-FILE. OPEN I-O PRODUCT-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening dynamic file: " FILE-STATUS STOP RUN END-IF DISPLAY "Dynamic file opened successfully". MAIN-MENU. PERFORM UNTIL MENU-CHOICE = 0 DISPLAY " " DISPLAY "=== Dynamic Access Menu ===" DISPLAY "1. Sequential Access (Read All Records)" DISPLAY "2. Indexed Access by Product ID" DISPLAY "3. Indexed Access by Product Name" DISPLAY "4. Relative Access by Record Number" DISPLAY "5. Add New Product" DISPLAY "6. Update Existing Product" DISPLAY "0. Exit" DISPLAY "Enter your choice: " WITH NO ADVANCING ACCEPT MENU-CHOICE EVALUATE MENU-CHOICE WHEN 1 PERFORM SEQUENTIAL-ACCESS WHEN 2 PERFORM INDEXED-ACCESS-BY-ID WHEN 3 PERFORM INDEXED-ACCESS-BY-NAME WHEN 4 PERFORM RELATIVE-ACCESS WHEN 5 PERFORM ADD-PRODUCT WHEN 6 PERFORM UPDATE-PRODUCT WHEN 0 DISPLAY "Exiting program..." WHEN OTHER DISPLAY "Invalid choice. Please try again." END-EVALUATE END-PERFORM. SEQUENTIAL-ACCESS. DISPLAY "=== Sequential Access Mode ===" MOVE "SEQUENTIAL" TO ACCESS-MODE START PRODUCT-FILE FIRST PERFORM UNTIL FILE-STATUS NOT = "00" READ PRODUCT-FILE NEXT AT END EXIT PERFORM NOT AT END DISPLAY "Product: " PRODUCT-ID " - " PRODUCT-NAME END-READ END-PERFORM. INDEXED-ACCESS-BY-ID. DISPLAY "=== Indexed Access by Product ID ===" DISPLAY "Enter Product ID: " WITH NO ADVANCING ACCEPT SEARCH-KEY MOVE SEARCH-KEY TO PRODUCT-ID READ PRODUCT-FILE INVALID KEY DISPLAY "Product ID " SEARCH-KEY " not found" NOT INVALID KEY DISPLAY "Product found:" DISPLAY " ID: " PRODUCT-ID DISPLAY " Name: " PRODUCT-NAME DISPLAY " Category: " PRODUCT-CATEGORY DISPLAY " Price: $" PRODUCT-PRICE DISPLAY " Stock: " PRODUCT-STOCK END-READ. INDEXED-ACCESS-BY-NAME. DISPLAY "=== Indexed Access by Product Name ===" DISPLAY "Enter Product Name: " WITH NO ADVANCING ACCEPT SEARCH-KEY MOVE SEARCH-KEY TO PRODUCT-NAME READ PRODUCT-FILE INVALID KEY DISPLAY "Product Name " SEARCH-KEY " not found" NOT INVALID KEY DISPLAY "Product found:" DISPLAY " ID: " PRODUCT-ID DISPLAY " Name: " PRODUCT-NAME DISPLAY " Category: " PRODUCT-CATEGORY DISPLAY " Price: $" PRODUCT-PRICE DISPLAY " Stock: " PRODUCT-STOCK END-READ. RELATIVE-ACCESS. DISPLAY "=== Relative Access Mode ===" DISPLAY "Enter record number: " WITH NO ADVANCING ACCEPT RECORD-POSITION READ PRODUCT-FILE INVALID KEY DISPLAY "Record number " RECORD-POSITION " not found" NOT INVALID KEY DISPLAY "Record found:" DISPLAY " Position: " RECORD-POSITION DISPLAY " ID: " PRODUCT-ID DISPLAY " Name: " PRODUCT-NAME DISPLAY " Category: " PRODUCT-CATEGORY DISPLAY " Price: $" PRODUCT-PRICE DISPLAY " Stock: " PRODUCT-STOCK END-READ. ADD-PRODUCT. DISPLAY "=== Add New Product ===" DISPLAY "Enter Product ID: " WITH NO ADVANCING ACCEPT PRODUCT-ID DISPLAY "Enter Product Name: " WITH NO ADVANCING ACCEPT PRODUCT-NAME DISPLAY "Enter Category: " WITH NO ADVANCING ACCEPT PRODUCT-CATEGORY DISPLAY "Enter Price: " WITH NO ADVANCING ACCEPT PRODUCT-PRICE DISPLAY "Enter Stock: " WITH NO ADVANCING ACCEPT PRODUCT-STOCK WRITE PRODUCT-RECORD INVALID KEY DISPLAY "Error adding product - duplicate ID" NOT INVALID KEY DISPLAY "Product added successfully" END-WRITE. UPDATE-PRODUCT. DISPLAY "=== Update Existing Product ===" DISPLAY "Enter Product ID to update: " WITH NO ADVANCING ACCEPT PRODUCT-ID READ PRODUCT-FILE INVALID KEY DISPLAY "Product ID " PRODUCT-ID " not found" NOT INVALID KEY DISPLAY "Current product information:" DISPLAY " Name: " PRODUCT-NAME DISPLAY " Category: " PRODUCT-CATEGORY DISPLAY " Price: $" PRODUCT-PRICE DISPLAY " Stock: " PRODUCT-STOCK DISPLAY " " DISPLAY "Enter new Price: " WITH NO ADVANCING ACCEPT PRODUCT-PRICE DISPLAY "Enter new Stock: " WITH NO ADVANCING ACCEPT PRODUCT-STOCK REWRITE PRODUCT-RECORD INVALID KEY DISPLAY "Error updating product" NOT INVALID KEY DISPLAY "Product updated successfully" END-REWRITE END-READ. CLOSE-FILE. CLOSE PRODUCT-FILE DISPLAY "Dynamic file closed successfully".

Performance Considerations

Choosing the right access method significantly impacts application performance. Understanding the performance characteristics of each method helps in making informed decisions.

Performance Comparison

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
* Performance characteristics of different access methods * Sequential Access Performance * - Best for: Processing entire files * - Time Complexity: O(n) for full file scan * - Memory Usage: Low * - Use When: Batch processing, reporting * Indexed Access Performance * - Best for: Finding specific records * - Time Complexity: O(log n) for key lookup * - Memory Usage: High (index overhead) * - Use When: Online transactions, lookups * Relative Access Performance * - Best for: Position-based access * - Time Complexity: O(1) for direct access * - Memory Usage: Moderate * - Use When: Array-like operations * Dynamic Access Performance * - Best for: Mixed access patterns * - Time Complexity: Varies by operation * - Memory Usage: High (multiple indexes) * - Use When: Complex applications

Optimization Strategies

  • Batch Processing: Use sequential access for large batch operations
  • Key Design: Choose efficient key structures for indexed access
  • Buffer Management: Optimize buffer sizes for your access pattern
  • Index Maintenance: Regular index reorganization for optimal performance
  • Access Pattern Analysis: Monitor and optimize based on actual usage

Best Practices for Access Methods

Following best practices ensures optimal performance and maintainability when implementing access methods in COBOL applications.

Design Guidelines

  • Choose access method based on primary usage patterns
  • Design keys for efficient access and uniqueness
  • Consider data growth and scalability requirements
  • Plan for error handling and recovery scenarios
  • Document access patterns and performance expectations

Implementation Best Practices

  • Always check file status after file operations
  • Implement proper error handling for all access methods
  • Use appropriate file organization for your access needs
  • Optimize record layouts for your access patterns
  • Test performance with realistic data volumes

Maintenance Considerations

  • Regular index maintenance and reorganization
  • Monitor file growth and performance trends
  • Plan for data migration and restructuring
  • Implement backup and recovery procedures
  • Document changes and their impact on access methods

Exercise: Multi-Access File System

Design and implement a comprehensive file system that demonstrates all access methods. The system should include:

  • Sequential processing for batch operations
  • Indexed access for quick lookups
  • Relative access for position-based operations
  • Dynamic access for complex operations
  • Performance monitoring and reporting

Consider these advanced requirements:

  • How would you handle concurrent access to the same file?
  • What strategies would you use for index optimization?
  • How would you implement data integrity checks?
  • What backup and recovery procedures would you include?

FAQ

What are access methods in COBOL?

Access methods in COBOL define how data is retrieved from files, including sequential access (reading records in order), indexed access (using keys), relative access (using record numbers), and random access (direct record retrieval).

What is the difference between sequential and indexed access in COBOL?

Sequential access reads records in the order they appear in the file, while indexed access uses key values to directly locate specific records. Sequential is faster for processing entire files, while indexed is faster for finding specific records.

How do you implement indexed access in COBOL?

Indexed access is implemented using the ACCESS MODE IS RANDOM or DYNAMIC clause in the SELECT statement, along with appropriate key definitions. Records are accessed using READ statements with key values.

What is relative access in COBOL?

Relative access allows reading records by their relative position in the file (record number). It's implemented using ACCESS MODE IS RANDOM with RELATIVE KEY, allowing direct access to records by their position.

How do you choose the right access method in COBOL?

Choose sequential access for processing entire files, indexed access for finding specific records by key, relative access for position-based retrieval, and random access for direct record access. Consider performance requirements and data access patterns.