MainframeMaster

COBOL Search Techniques Concepts

Search techniques in COBOL are methods for finding specific data within files, tables, or data structures efficiently. Understanding search techniques is essential for COBOL programming as most business applications require data lookup and retrieval operations. Proper search techniques ensure efficient data access, optimal performance, and reliable data retrieval.

Understanding Search Techniques

Search techniques in COBOL encompass all methods of locating specific data including sequential search, binary search, indexed search, and table search operations. Different search techniques are appropriate for different data organizations and performance requirements. Understanding these concepts is essential for choosing the right search approach for specific business requirements.

Sequential Search

1. File Sequential Search

Sequential search reads through file records one by one until the desired item is found. This method is simple but can be slow for large files or when searching for items near the end of the file.

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
DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(20). 05 CUSTOMER-BALANCE PIC 9(8)V99. WORKING-STORAGE SECTION. 01 SEARCH-CONTROLS. 05 SEARCH-ID PIC 9(5) VALUE 12345. 05 RECORD-FOUND PIC X(1) VALUE 'N'. 88 FOUND VALUE 'Y'. 88 NOT-FOUND VALUE 'N'. 05 SEARCH-COUNT PIC 9(6) VALUE 0. PROCEDURE DIVISION. SEQUENTIAL-FILE-SEARCH. DISPLAY 'Sequential File Search Example' OPEN INPUT CUSTOMER-FILE PERFORM UNTIL FILE-EOF OR FOUND READ CUSTOMER-FILE IF FILE-OK ADD 1 TO SEARCH-COUNT IF CUSTOMER-ID = SEARCH-ID SET FOUND TO TRUE DISPLAY 'Customer found: ' CUSTOMER-NAME DISPLAY 'Balance: ' CUSTOMER-BALANCE DISPLAY 'Records searched: ' SEARCH-COUNT END-IF END-IF END-PERFORM IF NOT-FOUND DISPLAY 'Customer not found: ' SEARCH-ID DISPLAY 'Total records searched: ' SEARCH-COUNT END-IF CLOSE CUSTOMER-FILE

Sequential file search reads records one by one until the target is found. This method is simple but can be inefficient for large files or when searching for items near the end.

2. Table Sequential Search

Table sequential search examines table entries one by one until the desired item is found. This method is useful for small tables or when the table is not sorted.

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-TABLE. 05 CUSTOMER-ENTRY OCCURS 100 TIMES. 10 CUSTOMER-ID PIC 9(5). 10 CUSTOMER-NAME PIC X(20). 10 CUSTOMER-BALANCE PIC 9(8)V99. 01 SEARCH-CONTROLS. 05 TABLE-SIZE PIC 9(3) VALUE 50. 05 SEARCH-ID PIC 9(5) VALUE 12345. 05 SEARCH-INDEX PIC 9(3) VALUE 0. 05 RECORD-FOUND PIC X(1) VALUE 'N'. 88 FOUND VALUE 'Y'. 88 NOT-FOUND VALUE 'N'. PROCEDURE DIVISION. SEQUENTIAL-TABLE-SEARCH. DISPLAY 'Sequential Table Search Example' *> Initialize table with sample data PERFORM INITIALIZE-CUSTOMER-TABLE *> Search for specific customer PERFORM SEARCH-CUSTOMER-TABLE IF FOUND DISPLAY 'Customer found at index: ' SEARCH-INDEX DISPLAY 'Name: ' CUSTOMER-NAME(SEARCH-INDEX) DISPLAY 'Balance: ' CUSTOMER-BALANCE(SEARCH-INDEX) ELSE DISPLAY 'Customer not found: ' SEARCH-ID END-IF. INITIALIZE-CUSTOMER-TABLE. PERFORM VARYING INIT-INDEX FROM 1 BY 1 UNTIL INIT-INDEX > TABLE-SIZE MOVE INIT-INDEX TO CUSTOMER-ID(INIT-INDEX) STRING 'Customer' DELIMITED BY SIZE INIT-INDEX DELIMITED BY SIZE INTO CUSTOMER-NAME(INIT-INDEX) END-STRING COMPUTE CUSTOMER-BALANCE(INIT-INDEX) = INIT-INDEX * 100.00 END-PERFORM. SEARCH-CUSTOMER-TABLE. MOVE 1 TO SEARCH-INDEX PERFORM UNTIL SEARCH-INDEX > TABLE-SIZE OR FOUND IF CUSTOMER-ID(SEARCH-INDEX) = SEARCH-ID SET FOUND TO TRUE ELSE ADD 1 TO SEARCH-INDEX END-IF END-PERFORM

Table sequential search examines table entries one by one until the target is found. This method is suitable for small tables or unsorted data.

Binary Search

1. Binary Search Algorithm

Binary search is an efficient search algorithm that divides a sorted dataset in half repeatedly to quickly locate a specific item. This method significantly reduces search time for large sorted datasets.

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 SORTED-TABLE. 05 TABLE-ENTRY OCCURS 1000 TIMES. 10 ENTRY-ID PIC 9(5). 10 ENTRY-NAME PIC X(20). 10 ENTRY-VALUE PIC 9(8)V99. 01 BINARY-SEARCH-CONTROLS. 05 TABLE-SIZE PIC 9(4) VALUE 1000. 05 SEARCH-ID PIC 9(5) VALUE 500. 05 LEFT-BOUND PIC 9(4) VALUE 1. 05 RIGHT-BOUND PIC 9(4). 05 MIDDLE-POINT PIC 9(4). 05 SEARCH-FOUND PIC X(1) VALUE 'N'. 88 FOUND VALUE 'Y'. 88 NOT-FOUND VALUE 'N'. PROCEDURE DIVISION. BINARY-SEARCH-EXAMPLE. DISPLAY 'Binary Search Example' *> Initialize sorted table PERFORM INITIALIZE-SORTED-TABLE *> Perform binary search PERFORM BINARY-SEARCH-ALGORITHM IF FOUND DISPLAY 'Item found at index: ' MIDDLE-POINT DISPLAY 'Name: ' ENTRY-NAME(MIDDLE-POINT) DISPLAY 'Value: ' ENTRY-VALUE(MIDDLE-POINT) ELSE DISPLAY 'Item not found: ' SEARCH-ID END-IF. INITIALIZE-SORTED-TABLE. PERFORM VARYING INIT-INDEX FROM 1 BY 1 UNTIL INIT-INDEX > TABLE-SIZE MOVE INIT-INDEX TO ENTRY-ID(INIT-INDEX) STRING 'Item' DELIMITED BY SIZE INIT-INDEX DELIMITED BY SIZE INTO ENTRY-NAME(INIT-INDEX) END-STRING COMPUTE ENTRY-VALUE(INIT-INDEX) = INIT-INDEX * 10.50 END-PERFORM. BINARY-SEARCH-ALGORITHM. MOVE TABLE-SIZE TO RIGHT-BOUND PERFORM UNTIL LEFT-BOUND > RIGHT-BOUND OR FOUND COMPUTE MIDDLE-POINT = (LEFT-BOUND + RIGHT-BOUND) / 2 IF ENTRY-ID(MIDDLE-POINT) = SEARCH-ID SET FOUND TO TRUE ELSE IF ENTRY-ID(MIDDLE-POINT) > SEARCH-ID COMPUTE RIGHT-BOUND = MIDDLE-POINT - 1 ELSE COMPUTE LEFT-BOUND = MIDDLE-POINT + 1 END-IF END-IF END-PERFORM

Binary search efficiently locates items in sorted data by repeatedly dividing the search space in half. This method provides logarithmic time complexity for large datasets.

2. SEARCH ALL Statement

The SEARCH ALL statement provides built-in binary search functionality for sorted tables, making it easy to implement efficient search operations.

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-TABLE. 05 CUSTOMER-ENTRY OCCURS 100 TIMES INDEXED BY CUSTOMER-INDEX. 10 CUSTOMER-ID PIC 9(5). 10 CUSTOMER-NAME PIC X(20). 10 CUSTOMER-BALANCE PIC 9(8)V99. 01 SEARCH-CONTROLS. 05 TABLE-SIZE PIC 9(3) VALUE 100. 05 SEARCH-ID PIC 9(5) VALUE 50. 05 SEARCH-FOUND PIC X(1) VALUE 'N'. 88 FOUND VALUE 'Y'. 88 NOT-FOUND VALUE 'N'. PROCEDURE DIVISION. SEARCH-ALL-EXAMPLE. DISPLAY 'SEARCH ALL Statement Example' *> Initialize sorted table PERFORM INITIALIZE-SORTED-CUSTOMER-TABLE *> Use SEARCH ALL for binary search SEARCH ALL CUSTOMER-ENTRY AT END SET NOT-FOUND TO TRUE DISPLAY 'Customer not found: ' SEARCH-ID WHEN CUSTOMER-ID(CUSTOMER-INDEX) = SEARCH-ID SET FOUND TO TRUE DISPLAY 'Customer found at index: ' CUSTOMER-INDEX DISPLAY 'Name: ' CUSTOMER-NAME(CUSTOMER-INDEX) DISPLAY 'Balance: ' CUSTOMER-BALANCE(CUSTOMER-INDEX) END-SEARCH. INITIALIZE-SORTED-CUSTOMER-TABLE. PERFORM VARYING INIT-INDEX FROM 1 BY 1 UNTIL INIT-INDEX > TABLE-SIZE MOVE INIT-INDEX TO CUSTOMER-ID(INIT-INDEX) STRING 'Customer' DELIMITED BY SIZE INIT-INDEX DELIMITED BY SIZE INTO CUSTOMER-NAME(INIT-INDEX) END-STRING COMPUTE CUSTOMER-BALANCE(INIT-INDEX) = INIT-INDEX * 100.00 END-PERFORM

The SEARCH ALL statement provides built-in binary search functionality for sorted tables. It automatically handles the binary search algorithm and provides efficient search operations.

Indexed Search

1. File Indexed Search

Indexed search uses file indexes to quickly locate records based on key values. This method provides fast random access to specific records without reading the entire file.

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
DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(20). 05 CUSTOMER-BALANCE PIC 9(8)V99. WORKING-STORAGE SECTION. 01 INDEXED-SEARCH-CONTROLS. 05 SEARCH-ID PIC 9(5) VALUE 12345. 05 FILE-STATUS PIC XX VALUE '00'. 88 FILE-OK VALUE '00'. 88 RECORD-FOUND VALUE '00'. 88 RECORD-NOT-FOUND VALUE '23'. PROCEDURE DIVISION. INDEXED-FILE-SEARCH. DISPLAY 'Indexed File Search Example' OPEN INPUT CUSTOMER-FILE *> Search using primary key MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE IF RECORD-FOUND DISPLAY 'Customer found: ' CUSTOMER-NAME DISPLAY 'Balance: ' CUSTOMER-BALANCE ELSE IF RECORD-NOT-FOUND DISPLAY 'Customer not found: ' SEARCH-ID ELSE DISPLAY 'File error: ' FILE-STATUS END-IF END-IF CLOSE CUSTOMER-FILE. ALTERNATE-KEY-SEARCH. DISPLAY 'Alternate Key Search Example' *> Search using alternate key (customer name) MOVE 'JOHN SMITH' TO CUSTOMER-NAME READ CUSTOMER-FILE IF RECORD-FOUND DISPLAY 'Customer found by name: ' CUSTOMER-ID DISPLAY 'Balance: ' CUSTOMER-BALANCE ELSE DISPLAY 'Customer not found by name' END-IF

Indexed file search uses file indexes to quickly locate records based on key values. This method provides efficient random access without sequential file reading.

2. Multiple Key Search

Multiple key search allows searching using different key fields, providing flexibility for various search criteria and business requirements.

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
PROCEDURE DIVISION. MULTIPLE-KEY-SEARCH. DISPLAY 'Multiple Key Search Example' *> Search by customer ID PERFORM SEARCH-BY-CUSTOMER-ID *> Search by customer name PERFORM SEARCH-BY-CUSTOMER-NAME *> Search by balance range PERFORM SEARCH-BY-BALANCE-RANGE. SEARCH-BY-CUSTOMER-ID. DISPLAY 'Searching by Customer ID' MOVE 12345 TO CUSTOMER-ID READ CUSTOMER-FILE IF RECORD-FOUND DISPLAY 'Found by ID: ' CUSTOMER-NAME ELSE DISPLAY 'Not found by ID' END-IF. SEARCH-BY-CUSTOMER-NAME. DISPLAY 'Searching by Customer Name' MOVE 'JOHN SMITH' TO CUSTOMER-NAME READ CUSTOMER-FILE IF RECORD-FOUND DISPLAY 'Found by name: ' CUSTOMER-ID ELSE DISPLAY 'Not found by name' END-IF. SEARCH-BY-BALANCE-RANGE. DISPLAY 'Searching by Balance Range' *> Use START to position at balance range MOVE 1000.00 TO CUSTOMER-BALANCE START CUSTOMER-FILE KEY IS GREATER THAN CUSTOMER-BALANCE *> Read records in balance range PERFORM UNTIL FILE-EOF READ CUSTOMER-FILE NEXT IF FILE-OK IF CUSTOMER-BALANCE > 1000.00 AND CUSTOMER-BALANCE < 5000.00 DISPLAY 'Customer in range: ' CUSTOMER-ID DISPLAY 'Balance: ' CUSTOMER-BALANCE END-IF END-IF END-PERFORM

Multiple key search provides flexibility by allowing searches using different key fields. This approach supports various business requirements and search criteria.

Search Optimization

1. Performance Optimization

Search performance optimization involves choosing appropriate search algorithms, using efficient data structures, and minimizing I/O operations for optimal performance.

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
PROCEDURE DIVISION. SEARCH-OPTIMIZATION-EXAMPLE. DISPLAY 'Search Optimization Example' *> Choose appropriate search method based on data size IF TABLE-SIZE < 100 PERFORM SEQUENTIAL-SEARCH ELSE IF TABLE-SIZE < 10000 PERFORM BINARY-SEARCH ELSE PERFORM INDEXED-SEARCH END-IF END-IF. SEQUENTIAL-SEARCH. DISPLAY 'Using sequential search for small table' PERFORM SEARCH-CUSTOMER-TABLE. BINARY-SEARCH. DISPLAY 'Using binary search for medium table' PERFORM BINARY-SEARCH-ALGORITHM. INDEXED-SEARCH. DISPLAY 'Using indexed search for large table' PERFORM INDEXED-FILE-SEARCH. OPTIMIZE-SEARCH-PERFORMANCE. DISPLAY 'Optimizing search performance' *> Cache frequently accessed data PERFORM CACHE-FREQUENT-DATA *> Use appropriate data structures PERFORM CHOOSE-OPTIMAL-DATA-STRUCTURE *> Minimize I/O operations PERFORM MINIMIZE-IO-OPERATIONS. CACHE-FREQUENT-DATA. DISPLAY 'Caching frequently accessed data' MOVE 'CACHE-ACTIVE' TO CACHE-STATUS. CHOOSE-OPTIMAL-DATA-STRUCTURE. DISPLAY 'Choosing optimal data structure' MOVE 'OPTIMIZED' TO STRUCTURE-STATUS. MINIMIZE-IO-OPERATIONS. DISPLAY 'Minimizing I/O operations' MOVE 'MINIMIZED' TO IO-STATUS

Search performance optimization involves choosing the right search algorithm based on data size, using efficient data structures, and minimizing I/O operations for optimal performance.

2. Search Strategy Selection

Search strategy selection involves choosing the most appropriate search method based on data characteristics, access patterns, and performance requirements.

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
PROCEDURE DIVISION. SEARCH-STRATEGY-SELECTION. DISPLAY 'Search Strategy Selection' *> Analyze data characteristics PERFORM ANALYZE-DATA-CHARACTERISTICS *> Determine access patterns PERFORM DETERMINE-ACCESS-PATTERNS *> Select optimal search strategy PERFORM SELECT-SEARCH-STRATEGY. ANALYZE-DATA-CHARACTERISTICS. DISPLAY 'Analyzing data characteristics' *> Check if data is sorted IF DATA-SORTED = 'Y' DISPLAY 'Data is sorted - binary search recommended' MOVE 'BINARY' TO RECOMMENDED-SEARCH ELSE DISPLAY 'Data is unsorted - sequential search required' MOVE 'SEQUENTIAL' TO RECOMMENDED-SEARCH END-IF *> Check data size IF DATA-SIZE < 100 DISPLAY 'Small dataset - sequential search efficient' ELSE IF DATA-SIZE < 10000 DISPLAY 'Medium dataset - binary search recommended' ELSE DISPLAY 'Large dataset - indexed search recommended' END-IF END-IF. DETERMINE-ACCESS-PATTERNS. DISPLAY 'Determining access patterns' *> Check if random access is needed IF RANDOM-ACCESS-NEEDED = 'Y' DISPLAY 'Random access required - indexed search recommended' MOVE 'INDEXED' TO RECOMMENDED-SEARCH ELSE DISPLAY 'Sequential access sufficient - sequential search OK' END-IF. SELECT-SEARCH-STRATEGY. DISPLAY 'Selecting search strategy: ' RECOMMENDED-SEARCH EVALUATE RECOMMENDED-SEARCH WHEN 'SEQUENTIAL' PERFORM IMPLEMENT-SEQUENTIAL-SEARCH WHEN 'BINARY' PERFORM IMPLEMENT-BINARY-SEARCH WHEN 'INDEXED' PERFORM IMPLEMENT-INDEXED-SEARCH END-EVALUATE

Search strategy selection analyzes data characteristics, access patterns, and performance requirements to choose the most appropriate search method for specific situations.

Best Practices for Search Techniques

Common Search Patterns