ContentsIndexPreviousNext

Code Examples

Code example 1:

In this example SEARCH is used to conduct a sequential search of the table for the first match. The index data item must be assigned an initial value by the program. Note that subsequent searches of the table for additional matches may be made if the value of the search index is saved after a match.

Assume the following table data item:

01  FRUIT-TREE-INVENTORY.
    05  FRUIT-TREE-TABLE
        OCCURS 100 TIMES
        INDEXED BY FTT-INDEX.
        10  FT-NAME    PIC X(25).
        10  FT-CODE    PIC X(5).
        10  FT-PRICE   PIC 9(5)V99.
        10  FT-COUNT   PIC 999.
*05 table name is specified by SEARCH
*OCCURS and INDEXED BY required for SEARCH

Assume that FRUIT-TREE-TABLE has been loaded.

*use SET to initialize the index
SET FTT-INDEX TO 1.
SEARCH FRUIT-TREE-TABLE
*handle no match in table
   AT END DISPLAY "Variety not found."
*test for match
   WHEN FT-NAME (FTT-INDEX) = TREE-NAME
*match found, perform action
      PERFORM DISPLAY-INVENTORY-ITEM
END-SEARCH.

Code example 2:

In this example a WHEN clause is used in a sequential search to test for an "end of table" (AT END equivalent) condition. Note that when the table being searched is not full (has table elements at the end that have not been filled), searching the table into the unfilled space will give unpredictable results. You can search a partially filled table by determining the position of the last valid entry in the table and then using a WHEN clause in the SEARCH statement to test for when the search process traverses past the last valid entry.

Assume the same table declaration as in example 1. Assume, also, that the program has verified the table entries and has saved the subscript value of the last valid entry in a variable named LAST-VALID-ENTRY.

*initialize the search index
SET FTT-INDEX TO 1.
SEARCH FRUIT-TREE-TABLE
*test for match
   WHEN FT-NAME (FTT-INDEX) = TREE-NAME
*match found, perform action
      PERFORM DISPLAY-INVENTORY-ITEM
*test for indexing into unfilled table space
   WHEN FTT-INDEX > LAST-VALID-ENTRY
*exit the SEARCH statement
      NEXT SENTENCE.

if ftt-index > last-valid-entry
      display " variety not found".

Code example 3:

In this example SEARCH ALL is used to conduct a binary search of an ordered table. Binary searches require sequential, ordered tables. The table definition must include an ASCENDING or DESCENDING KEY clause. The search terminates upon first match, and there is no way to continue the search to find a second match. Binary searches are best suited to large tables (typically 50 records or more). When used to search large tables, the binary search method will, on average, find a table record much more quickly than will a sequential search. For example, a table containing 1000 records will need to perform no more than ten comparisons to find a match.

Assume the following table data item:

01  FRUIT-TREE-INVENTORY.
    05 FRUIT-TREE-TABLE
*OCCURS required for SEARCH
      OCCURS 100 TIMES
*ASCENDING/DESCENDING KEY required
*for SEARCH ALL
      ASCENDING KEY IS FT-NAME
*INDEXED BY required for SEARCH
      INDEXED BY FTT-INDEX.
      10  FT-NAME    PIC X(25).
      10  FT-CODE    PIC X(5).
      10  FT-PRICE   PIC 9(5)V99.
      10  FT-COUNT   PIC 999.

Assume the table has been loaded.

*FTT-INDEX is initialized by SEARCH ALL
SEARCH ALL FRUIT-TREE-TABLE
*Handle no match in table.
    AT END DISPLAY "Variety not found"
*Test for match
    WHEN FT-NAME (FTT-INDEX) = TREE-NAME
*Match found, perform action
    PERFORM DISPLAY-INVENTORY-ITEM
END-SEARCH.

Code example 4:

This example demonstrates how to use SEARCH or SEARCH ALL to search multi-dimensional tables:

SEARCH is not, by itself, equipped to perform multi-dimensional table searches. One approach to accomplishing multi-dimensional table searches is to use SEARCH in conjunction with PERFORM/VARYING (as the following example will illustrate). When used together, SEARCH handles lookups at the innermost level (dimension) of the table structure and PERFORM/VARYING is used to manage stepping through the outer levels of the table.

Assume the following table data item:

01  TREE-INVENTORY.
    05  NURSERY-YARD                   |inventory location,
            OCCURS 10 TIMES            |"outer" table
            INDEXED BY YARD-IDX.
            10  TREE-TABLE             |tree type,
                   OCCURS 100 TIMES |"inner" table
                   INDEXED BY TT-IDX.
                15  FT-NAME       PIC X(25).
                15  FT-CODE       PIC X(5).
                15  FT-PRICE      PIC 9(5)V99.
                15  FT-COUNT      PIC 999.

Assume the table has been loaded.

MOVE "N" TO TREE-FOUND.
PERFORM SEARCH-TREE-INVENTORY
*step through the outer table
   VARYING YARD-IDX FROM 1 BY 1
      UNTIL YARD-IDX > 10 OR TREE-FOUND = "Y".

IF TREE-FOUND = "N"            |note that this code
   PERFORM NO-TREE-FOUND.      |executes after the
END-IF.                        |search is complete
{ . . . }
SEARCH-TREE-INVENTORY.
   SET TT-IDX TO 1.
   SEARCH TREE-TABLE
      WHEN TREE-TABLE(YARD-IDX,TT-IDX) = TREE-NAME

*note that both the inner and outer table
*indexes are required
         PERFORM DISPLAY-INVENTORY-ITEM
         MOVE "Y" TO TREE-FOUND
   END-SEARCH.

If the inner table is ordered and large enough to benefit from a binary search, use SEARCH ALL.