The SEARCH statement provides a powerful mechanism for sequentially searching through COBOL tables. It examines table elements one by one, testing each against specified conditions until either a match is found or the end of the table is reached.
123456SEARCH table-name [VARYING identifier] [AT END imperative-statement-1] WHEN condition-1 imperative-statement-2 [WHEN condition-2 imperative-statement-3] ... [END-SEARCH]
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647IDENTIFICATION DIVISION. PROGRAM-ID. TABLESRCH. DATA DIVISION. WORKING-STORAGE SECTION. 01 PRODUCT-TABLE. 05 PRODUCT-ENTRY OCCURS 10 TIMES INDEXED BY PROD-IDX. 10 PRODUCT-ID PIC X(5). 10 PRODUCT-NAME PIC X(20). 10 PRODUCT-PRICE PIC 9(4)V99. 10 PRODUCT-QUANTITY PIC 9(4). 01 SEARCH-ID PIC X(5). 01 FOUND-FLAG PIC X VALUE 'N'. 88 PRODUCT-FOUND VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. PERFORM INITIALIZE-TABLE DISPLAY "Enter product ID to search for: " ACCEPT SEARCH-ID SET PROD-IDX TO 1 SEARCH PRODUCT-ENTRY AT END DISPLAY "Product ID " SEARCH-ID " not found" WHEN PRODUCT-ID(PROD-IDX) = SEARCH-ID MOVE 'Y' TO FOUND-FLAG DISPLAY "Product found: " PRODUCT-NAME(PROD-IDX) DISPLAY "Price: $" PRODUCT-PRICE(PROD-IDX) DISPLAY "Quantity in stock: " PRODUCT-QUANTITY(PROD-IDX) END-SEARCH STOP RUN. INITIALIZE-TABLE. MOVE "P1001" TO PRODUCT-ID(1) MOVE "Desktop Computer" TO PRODUCT-NAME(1) MOVE 899.99 TO PRODUCT-PRICE(1) MOVE 25 TO PRODUCT-QUANTITY(1) MOVE "P1002" TO PRODUCT-ID(2) MOVE "Laptop" TO PRODUCT-NAME(2) MOVE 1299.99 TO PRODUCT-PRICE(2) MOVE 15 TO PRODUCT-QUANTITY(2) * Continue initializing the rest of the table...
This example demonstrates a basic sequential search through a product table. The SEARCH statement starts at the current index position (set to 1) and checks each element until either a matching product ID is found or the end of the table is reached.
1234567891011121314151617181920212223242526272829* Search with multiple WHEN clauses SEARCH PRODUCT-ENTRY AT END DISPLAY "No matching product found" WHEN PRODUCT-ID(PROD-IDX) = SEARCH-ID DISPLAY "Found by ID: " PRODUCT-NAME(PROD-IDX) WHEN PRODUCT-NAME(PROD-IDX) = SEARCH-NAME DISPLAY "Found by name: " PRODUCT-ID(PROD-IDX) END-SEARCH * Search with complex condition SEARCH PRODUCT-ENTRY AT END DISPLAY "No product in price range found" WHEN PRODUCT-PRICE(PROD-IDX) >= MIN-PRICE AND PRODUCT-PRICE(PROD-IDX) <= MAX-PRICE AND PRODUCT-QUANTITY(PROD-IDX) > 0 DISPLAY "Found product: " PRODUCT-NAME(PROD-IDX) DISPLAY "Price: $" PRODUCT-PRICE(PROD-IDX) END-SEARCH * Search with partial key matching SEARCH PRODUCT-ENTRY AT END DISPLAY "No product ID starting with P10 found" WHEN PRODUCT-ID(PROD-IDX)(1:3) = "P10" DISPLAY "Found product: " PRODUCT-ID(PROD-IDX) DISPLAY PRODUCT-NAME(PROD-IDX) END-SEARCH
These examples show more advanced uses of the SEARCH statement:
12345678910111213141516171819202122232401 ORDER-TABLE. 05 ORDER-ENTRY OCCURS 100 TIMES INDEXED BY ORD-IDX. 10 ORDER-ID PIC X(8). 10 CUSTOMER-ID PIC X(6). 10 ORDER-DATE PIC X(8). 10 ORDER-TOTAL PIC 9(5)V99. 01 ORDER-LIST-TABLE. 05 ORDER-LIST-ENTRY OCCURS 100 TIMES INDEXED BY LIST-IDX. 10 LIST-ORDER-ID PIC X(8). 10 LIST-STATUS PIC X. * Synchronize two tables during search SET ORD-IDX TO 1 SET LIST-IDX TO 1 SEARCH ORDER-ENTRY VARYING LIST-IDX AT END DISPLAY "Order not found" WHEN ORDER-ID(ORD-IDX) = SEARCH-ORDER-ID DISPLAY "Order found: " ORDER-ID(ORD-IDX) DISPLAY "Customer: " CUSTOMER-ID(ORD-IDX) DISPLAY "Status: " LIST-STATUS(LIST-IDX) END-SEARCH
The VARYING clause allows a secondary index or data item to be incremented along with the table's index. This is useful for synchronized searching in multiple tables or for keeping track of the position in different ways.
The SEARCH ALL statement performs a binary search on a table, which is significantly faster than sequential searching for large tables. Binary search divides the search space in half with each comparison, quickly narrowing down the location of the target element.
1234SEARCH ALL table-name [AT END imperative-statement-1] WHEN condition-1 [AND condition-2 ...] imperative-statement-2 [END-SEARCH]
1234567891001 CUSTOMER-TABLE. 05 CUSTOMER-COUNT PIC 9(4) COMP VALUE 100. 05 CUSTOMER-ENTRY OCCURS 100 TIMES ASCENDING KEY IS CUSTOMER-ID INDEXED BY CUST-IDX. 10 CUSTOMER-ID PIC X(6). 10 CUSTOMER-NAME PIC X(30). 10 CUSTOMER-ADDR PIC X(50). 10 CUSTOMER-PHONE PIC X(15). 10 CUSTOMER-CREDIT PIC 9(4)V99.
For a table to be searched with SEARCH ALL:
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849IDENTIFICATION DIVISION. PROGRAM-ID. BINSEARCH. DATA DIVISION. WORKING-STORAGE SECTION. 01 STATE-TABLE. 05 STATE-ENTRY OCCURS 50 TIMES ASCENDING KEY IS STATE-CODE INDEXED BY STATE-IDX. 10 STATE-CODE PIC XX. 10 STATE-NAME PIC X(20). 10 STATE-CAPITAL PIC X(20). 01 SEARCH-CODE PIC XX. 01 FOUND-FLAG PIC X VALUE 'N'. 88 STATE-FOUND VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. PERFORM INITIALIZE-TABLE DISPLAY "Enter state code to search for: " ACCEPT SEARCH-CODE SEARCH ALL STATE-ENTRY AT END DISPLAY "State code " SEARCH-CODE " not found" WHEN STATE-CODE(STATE-IDX) = SEARCH-CODE MOVE 'Y' TO FOUND-FLAG DISPLAY "State: " STATE-NAME(STATE-IDX) DISPLAY "Capital: " STATE-CAPITAL(STATE-IDX) END-SEARCH STOP RUN. INITIALIZE-TABLE. * Note: Data must be in ASCENDING order by STATE-CODE MOVE "AL" TO STATE-CODE(1) MOVE "Alabama" TO STATE-NAME(1) MOVE "Montgomery" TO STATE-CAPITAL(1) MOVE "AK" TO STATE-CODE(2) MOVE "Alaska" TO STATE-NAME(2) MOVE "Juneau" TO STATE-CAPITAL(2) MOVE "AZ" TO STATE-CODE(3) MOVE "Arizona" TO STATE-NAME(3) MOVE "Phoenix" TO STATE-CAPITAL(3) * Continue with all state codes in ascending order...
This example demonstrates a binary search using SEARCH ALL on a table of US states. The table is sorted by state code, which is specified as the key in the table definition. The binary search quickly finds the matching state based on the provided code.
12345678910111213141516171819202101 EMPLOYEE-TABLE. 05 EMPLOYEE-ENTRY OCCURS 1000 TIMES ASCENDING KEY IS EMP-DEPT-ID, EMP-ID INDEXED BY EMP-IDX. 10 EMP-DEPT-ID PIC X(3). 10 EMP-ID PIC X(6). 10 EMP-NAME PIC X(30). 10 EMP-POSITION PIC X(20). 10 EMP-SALARY PIC 9(6)V99. * Search for employee using both department and employee ID SEARCH ALL EMPLOYEE-ENTRY AT END DISPLAY "Employee not found" WHEN EMP-DEPT-ID(EMP-IDX) = SEARCH-DEPT AND EMP-ID(EMP-IDX) = SEARCH-EMP-ID DISPLAY "Employee found: " EMP-NAME(EMP-IDX) DISPLAY "Position: " EMP-POSITION(EMP-IDX) DISPLAY "Salary: $" EMP-SALARY(EMP-IDX) END-SEARCH
This example shows a table with multiple keys. The table must be sorted first by department ID and then by employee ID within each department. The SEARCH ALL statement includes conditions for both keys connected by AND.
Constraint | Description |
---|---|
Sorted Table Requirement | The table must be sorted according to the key fields specified in the ASCENDING/DESCENDING KEY clause. |
Condition Limitations | WHEN conditions can only test for equality (=) and must use the key fields defined in the table. |
Multiple Keys | Multiple conditions must be connected by AND, not OR, and must follow the same order as the keys in the table definition. |
No VARYING Clause | SEARCH ALL does not support the VARYING clause since it doesn't perform sequential access. |
No Index Manipulation | There's no need to SET the index before SEARCH ALL; it automatically starts at the beginning of the table. |
Partial Key Limitations | You cannot use reference modification or substring operations with SEARCH ALL. |
Feature | SEARCH | SEARCH ALL |
---|---|---|
Algorithm | Sequential/linear search | Binary search |
Performance | O(n) - proportional to table size | O(log n) - much faster for large tables |
Table Requirements | Requires INDEXED BY | Requires INDEXED BY and ASCENDING/DESCENDING KEY |
Data Ordering | Can search unsorted tables | Table must be sorted by the key fields |
Starting Position | Starts from current index position | Always searches the entire table |
Condition Flexibility | Allows any conditions, including ranges, inequalities, and complex logic | Limited to equality conditions on key fields |
VARYING Clause | Supports VARYING for synchronizing with other indexes | Does not support VARYING |
Best Use Cases | Small tables, unsorted data, complex search conditions | Large tables, sorted data, simple key-based lookups |
The SET statement is essential for working with table indexes in COBOL. It allows programmers to position indexes at specific table elements, copy index values, and perform various index manipulation operations needed for efficient table handling.
12345678910* Format 1: Setting indexes to specific values SET index-name-1 [index-name-2 ...] TO {integer-1 | identifier-1} * Format 2: Setting indexes to the same value as another index SET index-name-1 [index-name-2 ...] TO index-name-3 * Format 3: Incrementing or decrementing indexes SET index-name-1 [index-name-2 ...] {UP BY | DOWN BY} {integer-1 | identifier-1}
12345678910111213141516171819202101 PRODUCT-TABLE. 05 PRODUCT-ENTRY OCCURS 100 TIMES INDEXED BY PROD-IDX, ALT-IDX. 10 PRODUCT-ID PIC X(5). 10 PRODUCT-NAME PIC X(20). 10 PRODUCT-PRICE PIC 9(4)V99. 01 TABLE-POSITION PIC 9(3) VALUE 1. * Set index to a specific occurrence SET PROD-IDX TO 1 * Set to first occurrence SET PROD-IDX TO 50 * Set to 50th occurrence SET PROD-IDX TO TABLE-POSITION * Set to position from variable * Set one index to same value as another SET ALT-IDX TO PROD-IDX * Copy index value * Increment or decrement an index SET PROD-IDX UP BY 1 * Move to next element SET PROD-IDX UP BY 10 * Skip ahead 10 elements SET PROD-IDX DOWN BY 5 * Move back 5 elements SET PROD-IDX UP BY INCREMENT-VAL * Move by variable amount
These examples illustrate the three primary ways to use the SET statement with indexes: setting to a specific occurrence number, copying from another index, and incrementing or decrementing by a specified amount.
123456789101112131415161718192021222324252627282901 CUSTOMER-TABLE. 05 CUSTOMER-ENTRY OCCURS 500 TIMES INDEXED BY CUST-IDX, SAVE-IDX, TEMP-IDX. 10 CUSTOMER-ID PIC X(6). 10 CUSTOMER-NAME PIC X(30). * Set multiple indexes at once SET CUST-IDX, SAVE-IDX, TEMP-IDX TO 1 * Save and restore index positions PERFORM FIND-CUSTOMER SET SAVE-IDX TO CUST-IDX * Save current position PERFORM OTHER-PROCESSING SET CUST-IDX TO SAVE-IDX * Restore position * Comparing index positions IF CUST-IDX = SAVE-IDX DISPLAY "Indexes at same position" END-IF * Managing multiple pointers in a table SET CUST-IDX TO 1 * Beginning of list SET SAVE-IDX TO 500 * End of list * Swap index values SET TEMP-IDX TO CUST-IDX SET CUST-IDX TO SAVE-IDX SET SAVE-IDX TO TEMP-IDX
Multiple indexes can be defined for a single table to maintain different positions or pointers within the table. This example shows various techniques for working with multiple indexes, including setting them as a group and swapping values.
Feature | Index | Subscript |
---|---|---|
Declaration | Defined using INDEXED BY in the OCCURS clause | Any numeric data item can be used as a subscript |
Storage | Special internal format optimized for table access | Regular numeric data item |
Manipulation | SET statement only | Any arithmetic statement (ADD, SUBTRACT, etc.) |
Performance | Faster, optimized by compiler | Slower, requires conversion to displacement |
Portability | Internal format may vary between compilers | Consistent representation |
Usage in Expressions | Cannot be used in calculations | Can be used in any arithmetic expression |
Usage with SEARCH | Required for SEARCH and SEARCH ALL | Not usable with SEARCH statements |
1234567891011121314151617* Example showing both index and subscript usage 01 DATA-TABLE. 05 DATA-ITEM OCCURS 100 TIMES INDEXED BY DATA-IDX. 10 ITEM-VALUE PIC X(10). 01 SUBSCRIPT-1 PIC 9(3) VALUE 1. * Using an index SET DATA-IDX TO 50 DISPLAY ITEM-VALUE(DATA-IDX) SET DATA-IDX UP BY 1 DISPLAY ITEM-VALUE(DATA-IDX) * Using a subscript MOVE 50 TO SUBSCRIPT-1 DISPLAY ITEM-VALUE(SUBSCRIPT-1) ADD 1 TO SUBSCRIPT-1
This example illustrates the difference in syntax between using indexes and subscripts. While the end result is the same, indexes offer better performance and are required for the SEARCH statements.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970* Comprehensive example of table processing with indexes IDENTIFICATION DIVISION. PROGRAM-ID. INDEXDEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 STUDENT-TABLE. 05 STUDENT-COUNT PIC 9(3) VALUE 10. 05 STUDENT-ENTRY OCCURS 50 TIMES INDEXED BY STUD-IDX, PREV-IDX, NEXT-IDX. 10 STUDENT-ID PIC X(6). 10 STUDENT-NAME PIC X(30). 10 STUDENT-GRADE PIC 9(3). 01 PROCESSING-VARS. 05 CURRENT-POSITION PIC 9(3). 05 HIGHEST-GRADE PIC 9(3) VALUE ZERO. 05 LOWEST-GRADE PIC 9(3) VALUE 999. 05 TOP-STUDENT-IDX PIC 9(3). 05 BOTTOM-STUDENT-IDX PIC 9(3). PROCEDURE DIVISION. MAIN-LOGIC. PERFORM INITIALIZE-TABLE PERFORM PROCESS-GRADES PERFORM DISPLAY-RESULTS STOP RUN. INITIALIZE-TABLE. * Table initialization code here... PROCESS-GRADES. * Find highest and lowest grades using indexes SET STUD-IDX TO 1 PERFORM VARYING STUD-IDX FROM 1 BY 1 UNTIL STUD-IDX > STUDENT-COUNT IF STUDENT-GRADE(STUD-IDX) > HIGHEST-GRADE MOVE STUDENT-GRADE(STUD-IDX) TO HIGHEST-GRADE MOVE STUD-IDX TO TOP-STUDENT-IDX END-IF IF STUDENT-GRADE(STUD-IDX) < LOWEST-GRADE MOVE STUDENT-GRADE(STUD-IDX) TO LOWEST-GRADE MOVE STUD-IDX TO BOTTOM-STUDENT-IDX END-IF END-PERFORM * Use SET to position at top and bottom students SET STUD-IDX TO TOP-STUDENT-IDX DISPLAY "Top student: " STUDENT-NAME(STUD-IDX) DISPLAY "Grade: " STUDENT-GRADE(STUD-IDX) SET STUD-IDX TO BOTTOM-STUDENT-IDX DISPLAY "Bottom student: " STUDENT-NAME(STUD-IDX) DISPLAY "Grade: " STUDENT-GRADE(STUD-IDX). DISPLAY-RESULTS. * Build linked list structure with indexes SET STUD-IDX TO 1 PERFORM VARYING STUD-IDX FROM 1 BY 1 UNTIL STUD-IDX >= STUDENT-COUNT SET NEXT-IDX TO STUD-IDX SET NEXT-IDX UP BY 1 * Save previous index SET PREV-IDX TO STUD-IDX * Advance to next element SET STUD-IDX TO NEXT-IDX END-PERFORM.
This comprehensive example demonstrates advanced table processing using multiple indexes. It shows how to traverse a table, find values based on conditions, and even simulate a linked-list structure using multiple indexes.
Proper table initialization and optimization are critical for efficient COBOL applications. This section covers various techniques for initializing tables and optimizing table operations for better performance.
There are several ways to initialize tables in COBOL, each with its own advantages:
123456789101112131415161701 MONTH-TABLE. 05 MONTH-NAMES. 10 FILLER PIC X(9) VALUE "January". 10 FILLER PIC X(9) VALUE "February". 10 FILLER PIC X(9) VALUE "March". 10 FILLER PIC X(9) VALUE "April". 10 FILLER PIC X(9) VALUE "May". 10 FILLER PIC X(9) VALUE "June". 10 FILLER PIC X(9) VALUE "July". 10 FILLER PIC X(9) VALUE "August". 10 FILLER PIC X(9) VALUE "September". 10 FILLER PIC X(9) VALUE "October". 10 FILLER PIC X(9) VALUE "November". 10 FILLER PIC X(9) VALUE "December". 05 MONTH-NAME-TABLE REDEFINES MONTH-NAMES. 10 MONTH-NAME PIC X(9) OCCURS 12 TIMES INDEXED BY MONTH-IDX.
This approach uses FILLER items with individual VALUE clauses and then redefines the area as a table. It is useful for tables with string or non-uniform values.
123401 DAYS-IN-MONTH-TABLE. 05 DAYS-IN-MONTH OCCURS 12 TIMES PIC 99 VALUES 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31.
For elementary items, the VALUE clause can include a list of values for each table element. This is concise but only works for simple tables of elementary items.
12345678910111213141516171819202122232401 STATE-TABLE. 05 STATE-ENTRY OCCURS 3 TIMES INDEXED BY STATE-IDX. 10 STATE-CODE PIC XX. 10 STATE-NAME PIC X(20). 10 STATE-CAPITAL PIC X(20). 10 STATE-POPULATION PIC 9(8). 01 STATE-VALUES. 05 FILLER PIC X(50) VALUE "NYNEW YORK ALBANY 19500000". 05 FILLER PIC X(50) VALUE "CAOALIFORNIA SACRAMENTO 39500000". 05 FILLER PIC X(50) VALUE "TXTEXAS AUSTIN 29000000". 01 STATE-VALUE-TABLE REDEFINES STATE-VALUES. 05 STATE-VALUE-ENTRY PIC X(50) OCCURS 3 TIMES. PROCEDURE DIVISION. INITIALIZATION. PERFORM VARYING STATE-IDX FROM 1 BY 1 UNTIL STATE-IDX > 3 MOVE STATE-VALUE-ENTRY(STATE-IDX) TO STATE-ENTRY(STATE-IDX) END-PERFORM.
This technique uses a separate table of string values that are then moved to the main table in the PROCEDURE DIVISION. It's useful for complex tables with multiple fields.
123456789101112131415161718192001 EMPLOYEE-TABLE. 05 EMPLOYEE-ENTRY OCCURS 100 TIMES INDEXED BY EMP-IDX. 10 EMP-ID PIC X(6). 10 EMP-NAME PIC X(30). 10 EMP-SALARY PIC 9(6)V99. 10 EMP-HIRE-DATE PIC X(8). 10 EMP-DEPT PIC X(4). * Initialize the entire table INITIALIZE EMPLOYEE-TABLE * Initialize with specific values INITIALIZE EMPLOYEE-TABLE REPLACING NUMERIC DATA BY ZERO ALPHANUMERIC DATA BY SPACES * Initialize a specific element SET EMP-IDX TO 1 INITIALIZE EMPLOYEE-ENTRY(EMP-IDX)
The INITIALIZE statement provides a way to set default values for an entire table or specific elements. It's useful for clearing or resetting tables.
123456789101112131415161718* Programmatic initialization with a loop PERFORM VARYING EMP-IDX FROM 1 BY 1 UNTIL EMP-IDX > 100 MOVE SPACES TO EMP-ID(EMP-IDX) MOVE SPACES TO EMP-NAME(EMP-IDX) MOVE ZEROS TO EMP-SALARY(EMP-IDX) MOVE "19000101" TO EMP-HIRE-DATE(EMP-IDX) MOVE "NONE" TO EMP-DEPT(EMP-IDX) END-PERFORM * Initialization from a file OPEN INPUT EMPLOYEE-FILE PERFORM VARYING EMP-IDX FROM 1 BY 1 UNTIL EMP-IDX > 100 OR END-OF-FILE READ EMPLOYEE-FILE INTO EMPLOYEE-ENTRY(EMP-IDX) AT END SET END-OF-FILE TO TRUE END-READ END-PERFORM CLOSE EMPLOYEE-FILE
Programmatic initialization using PERFORM loops offers the most flexibility, especially for dynamic initialization or loading data from external sources.
1234567891011121314151617181920212223242526272801 TRANSACTION-TABLE. 05 TRANSACTION-COUNT PIC 9(4) COMP VALUE ZERO. 05 TRANSACTION-ENTRY OCCURS 0 TO 1000 TIMES DEPENDING ON TRANSACTION-COUNT INDEXED BY TRANS-IDX. 10 TRANS-ID PIC X(8). 10 TRANS-DATE PIC X(8). 10 TRANS-AMOUNT PIC 9(7)V99. * Reading transactions into a variable-length table MOVE ZERO TO TRANSACTION-COUNT OPEN INPUT TRANSACTION-FILE PERFORM UNTIL END-OF-FILE OR TRANSACTION-COUNT >= 1000 READ TRANSACTION-FILE INTO WS-TRANSACTION-RECORD AT END SET END-OF-FILE TO TRUE NOT AT END ADD 1 TO TRANSACTION-COUNT MOVE WS-TRANS-ID TO TRANS-ID(TRANSACTION-COUNT) MOVE WS-TRANS-DATE TO TRANS-DATE(TRANSACTION-COUNT) MOVE WS-TRANS-AMOUNT TO TRANS-AMOUNT(TRANSACTION-COUNT) END-READ END-PERFORM CLOSE TRANSACTION-FILE DISPLAY "Loaded " TRANSACTION-COUNT " transactions"
Variable-length tables using the OCCURS DEPENDING ON clause allow more efficient memory usage, especially when the actual number of elements is not known in advance. The table size is determined by the value of the specified data item (TRANSACTION-COUNT in this example).
12345678910111213* Bad practice: Multiple sequential searches PERFORM FIND-CUSTOMER PERFORM FIND-CUSTOMER-ORDERS PERFORM FIND-CUSTOMER-PAYMENTS * Better practice: Caching index position PERFORM FIND-CUSTOMER IF CUSTOMER-FOUND SET SAVE-IDX TO CUST-IDX PERFORM FIND-CUSTOMER-ORDERS SET CUST-IDX TO SAVE-IDX PERFORM FIND-CUSTOMER-PAYMENTS END-IF
Minimize repeated searches by saving index positions when a table element is found, especially for related operations on the same data.
1234567891011121314151617* Use SEARCH ALL instead of SEARCH for large sorted tables * Sequential search - O(n) complexity SET CUST-IDX TO 1 SEARCH CUSTOMER-ENTRY AT END DISPLAY "Customer not found" WHEN CUSTOMER-ID(CUST-IDX) = SEARCH-ID DISPLAY "Customer found" END-SEARCH * Binary search - O(log n) complexity - much faster for large tables SEARCH ALL CUSTOMER-ENTRY AT END DISPLAY "Customer not found" WHEN CUSTOMER-ID(CUST-IDX) = SEARCH-ID DISPLAY "Customer found" END-SEARCH
For large tables that are accessed frequently, ensure they are sorted and use SEARCH ALL (binary search) instead of SEARCH for dramatically improved performance.
1234567891011121314151617181920212223242501 NESTED-TABLE. 05 DEPARTMENT OCCURS 10 TIMES INDEXED BY DEPT-IDX. 10 DEPT-ID PIC X(3). 10 DEPT-NAME PIC X(20). 10 EMPLOYEE OCCURS 50 TIMES INDEXED BY EMP-IDX. 15 EMP-ID PIC X(6). 15 EMP-NAME PIC X(30). * Inefficient: Resetting inner index for each outer element PERFORM VARYING DEPT-IDX FROM 1 BY 1 UNTIL DEPT-IDX > 10 PERFORM VARYING EMP-IDX FROM 1 BY 1 UNTIL EMP-IDX > 50 * Process employees END-PERFORM END-PERFORM * More efficient: Reset inner index only once per outer element PERFORM VARYING DEPT-IDX FROM 1 BY 1 UNTIL DEPT-IDX > 10 SET EMP-IDX TO 1 PERFORM UNTIL EMP-IDX > 50 * Process employees SET EMP-IDX UP BY 1 END-PERFORM END-PERFORM
For nested tables, manage indexes efficiently to avoid unnecessary resets and optimize the traversal pattern based on how the data is accessed.
1234567891011121314151617181920212223242526272829303132333435363738* Create an index table for sorted access without reordering the main table 01 CUSTOMER-TABLE. 05 CUSTOMER-ENTRY OCCURS 1000 TIMES INDEXED BY CUST-IDX. 10 CUSTOMER-ID PIC X(6). 10 CUSTOMER-NAME PIC X(30). 10 CUSTOMER-DATA PIC X(100). * Index table sorted by CUSTOMER-NAME 01 NAME-INDEX-TABLE. 05 NAME-INDEX OCCURS 1000 TIMES INDEXED BY NAME-IDX. 10 NAME-CUSTOMER-IDX PIC 9(4). * Build the index table PERFORM VARYING CUST-IDX FROM 1 BY 1 UNTIL CUST-IDX > 1000 MOVE CUST-IDX TO NAME-CUSTOMER-IDX(CUST-IDX) END-PERFORM * Sort the index table based on customer names (bubble sort example) PERFORM VARYING OUTER-IDX FROM 1 BY 1 UNTIL OUTER-IDX > 999 PERFORM VARYING INNER-IDX FROM 1 BY 1 UNTIL INNER-IDX > 1000 - OUTER-IDX SET CUST-IDX TO NAME-CUSTOMER-IDX(INNER-IDX) SET NEXT-CUST-IDX TO NAME-CUSTOMER-IDX(INNER-IDX + 1) IF CUSTOMER-NAME(CUST-IDX) > CUSTOMER-NAME(NEXT-CUST-IDX) MOVE NAME-CUSTOMER-IDX(INNER-IDX) TO TEMP-IDX MOVE NAME-CUSTOMER-IDX(INNER-IDX + 1) TO NAME-CUSTOMER-IDX(INNER-IDX) MOVE TEMP-IDX TO NAME-CUSTOMER-IDX(INNER-IDX + 1) END-IF END-PERFORM END-PERFORM * Access customer data in name order without reordering the main table PERFORM VARYING NAME-IDX FROM 1 BY 1 UNTIL NAME-IDX > 1000 SET CUST-IDX TO NAME-CUSTOMER-IDX(NAME-IDX) DISPLAY CUSTOMER-NAME(CUST-IDX) END-PERFORM
Using index tables allows for different sorted views of the same data without duplicating or reordering the main table, which is especially useful for large tables that need to be accessed in multiple ways.
12345678910111213* Main program passes only the needed portion of a large table CALL "PROCESS-REGION" USING REGION-TABLE(CURRENT-REGION) * Subprogram receives just the relevant section LINKAGE SECTION. 01 LS-REGION. 05 REGION-ID PIC X(2). 05 REGION-NAME PIC X(20). 05 REGION-CUSTOMERS OCCURS 1000 TIMES INDEXED BY LS-CUST-IDX. 10 LS-CUSTOMER-DATA PIC X(200). PROCEDURE DIVISION USING LS-REGION.
When working with very large tables, consider passing only the necessary sections to subprograms to reduce memory usage and improve performance.
1. What statement is used for sequential search in COBOL tables?
2. Which COBOL statement performs a binary search on a table?
3. What is required for a table to be searched using SEARCH ALL?
4. What statement is used to set the value of an index for a table?
5. What is the advantage of using indexes over subscripts when working with COBOL tables?
Detailed usage of the SEARCH statement for sequential searches.
Binary searching in COBOL tables using SEARCH ALL.
Defining tables in COBOL with the OCCURS clause.
Using the SET statement to manipulate indexes.
Accessing parts of table elements using reference modification.