Compaq COBOL
User Manual


Previous Contents Index

4.2 Initializing Values of Table Elements

You can initialize a table that contains only DISPLAY items to any desired value in either of the following ways:

Example 4-11 and Figure 4-10 provide an example and memory map of a table initialized using the VALUE clause.

Example 4-11 Initializing Tables with the VALUE Clause

01 A-TABLE VALUE IS "JANFEBMARAPRMAYJUNJULAUGSEPOCTNOVDEC". 
    03 MONTH-GROUP PIC XXX USAGE DISPLAY 
               OCCURS 12 TIMES. 

Figure 4-10 Memory Map for Example on Initializing Tables with the VALUE Clause


If each entry in the table has the same value, you can initialize the table as shown in Example 4-12.

Example 4-12 Initializing a Table with the OCCURS Clause

01 A-TABLE. 
   03 TABLE-LEG OCCURS 5 TIMES. 
      05 FIRST-LEG   PIC X VALUE "A". 
      05 SECOND-LEG  PIC S9(9) COMP VALUE 5. 

In this example, there are five occurrences of each table element. Each element is initialized to the same value as follows:

Often a table is too long to initialize using a single literal, or it contains numeric, alphanumeric, COMP, COMP-1, COMP-2, or COMP SYNC items that cannot be initialized. In these situations, you can initialize individual items by redefining the group level that precedes the level containing the OCCURS clause. Consider the sample table descriptions illustrated in Example 4-13 and Example 4-14. Each fill byte between ITEM1 and ITEM2 in Example 4-13 is initialized to X. Figure 4-11 shows how this is mapped into memory.

Example 4-13 Initializing Mixed Usage Items

01 A-RECORD-ALT. 
   05 FILLER PIC XX VALUE "AX". 
   05 FILLER PIC S99 COMP VALUE 1. 
   05 FILLER PIC XX VALUE "BX". 
   05 FILLER PIC S99 COMP VALUE 2. 
   . 
   . 
   . 
01 A-RECORD REDEFINES A-RECORD-ALT. 
   03 A-GROUP OCCURS 26 TIMES. 
      05 ITEM1 PIC X. 
      05 ITEM2 PIC S99 COMP SYNC. 

Figure 4-11 Memory Map for Example on Initializing Mixed Usage Items


As shown in Example 4-14 and in Figure 4-12, each FILLER item initializes three 10-byte table elements.

Example 4-14 Initializing Alphanumeric Items

01 A-RECORD-ALT. 
    03 FILLER PIC X(30) VALUE IS 
       "AAAAAAAAAABBBBBBBBBBCCCCCCCCCC". 
    03 FILLER PIC X(30) VALUE IS 
       "DDDDDDDDDDEEEEEEEEEEFFFFFFFFFF". 
    . 
    . 
    . 
01 A-RECORD REDEFINES A-RECORD-ALT. 
    03 ITEM1 PIC X(10) OCCURS 26 TIMES. 

Figure 4-12 Memory Map for Example on Initializing Alphanumeric Items


When redefining or initializing table elements, allow space for any fill bytes that may be added due to synchronization. You do not have to initialize fill bytes, but you can do so. If you initialize fill bytes to an uncommon value, you can use them as a debugging aid in situations where a Procedure Division statement refers to the record level preceding the OCCURS clause, or to another record redefining that level.

You can also initialize tables at run time. To initialize tables at run time, use the INITIALIZE statement. This statement allows you to initialize all occurrences of a table element to the same value. For more information about the INITIALIZE statement, refer to the Compaq COBOL Reference Manual.

Sometimes the length and format of table items are such that they are best initialized using Procedure Division statements such as a MOVE statement to send a value to the table.

4.3 Accessing Table Elements

Once tables have been created using the OCCURS clause, the program must have a method of accessing the individual elements of those tables. Subscripting and indexing are the two methods Compaq COBOL provides for accessing individual table elements. To refer to a particular element within a table, follow the name of that element with a subscript or index enclosed in parentheses. The following sections describe how to identify and access table elements using subscripts and indexes.

4.3.1 Subscripting

A subscript can be an integer literal, an arithmetic expression, a data name, or a subscripted data name that has an integer value. The integer value represents the desired element of the table. An integer value of 3, for example, refers to the third element of a table.

4.3.2 Subscripting with Literals

A literal subscript is an integer value, enclosed in parentheses, that represents the desired table element. In Example 4-15, the literal subscript (2) in the MOVE instruction moves the contents of the second element of A-TABLE to I-RECORD.

Example 4-15 Using a Literal Subscript to Access a Table

Table Description:
 
      01 A-TABLE. 
         03 A-GROUP PIC X(5) 
            OCCURS 10 TIMES. 
 
Instruction:
 
         MOVE A-GROUP(2) TO I-RECORD. 

If the table is multidimensional, follow the data name of the desired data item with a list of subscripts, one for each OCCURS clause to which the item is subordinate. The first subscript in the list applies to the first OCCURS clause to which that item is subordinate. This is the most inclusive level, and is represented by A-GROUP in Example 4-16. The second subscript applies to the next most inclusive level and is represented by ITEM3 in the example. Finally, the third subscript applies to the least inclusive level, represented by ITEM5. (Note that Compaq COBOL can have 48 subscripts that follow the pattern in Example 4-15.)

In Example 4-16, the subscripts (2,11,3) in the MOVE statements move the third occurrence of ITEM5 in the eleventh repetition of ITEM3 in the second repetition of A-GROUP to I-FIELD5. ITEM5(1,1,1) refers to the first occurrence of ITEM5 in the table, and ITEM5(5,20,4) refers to the last occurrence of ITEM5.

Example 4-16 Subscripting a Multidimensional Table

Table Description:
 
      01 A-TABLE. 
         03 A-GROUP OCCURS 5 TIMES. 
            05 ITEM1           PIC X. 
            05 ITEM2           PIC 99 COMP OCCURS 20 TIMES. 
            05 ITEM3 OCCURS 20 TIMES. 
               07 ITEM4        PIC X. 
               07 ITEM5        PIC XX OCCURS 4 TIMES. 
      01 I-FIELD5              PIC XX. 
 
Procedural Instruction:
 
            MOVE ITEM5(2, 11, 3) TO I-FIELD5. 

Note

Because ITEM5 is not subordinate to ITEM2, an occurrence number for ITEM2 is not permitted in the subscript list (when referencing ITEM3, ITEM4, or ITEM5). The ninth occurrence of ITEM2 in the fifth occurrence of A-GROUP will be selected by ITEM2(5,9).

Table 4-1 shows the subscripting rules that apply to Example 4-16.

Table 4-1 Subscripting Rules for a Multidimensional Table
Name of Item Number of Subscripts
Required to Refer to
the Name Item
Size of Item in Bytes
(Each Occurrence)
A-TABLE NONE 1105
A-GROUP ONE 221
ITEM1 ONE 1
ITEM2 TWO 2
ITEM3 TWO 9
ITEM4 TWO 1
ITEM5 THREE 2

4.3.3 Subscripting with Data Names

You can also use data names to specify subscripts. To use a data name as a subscript, define it with COMP, COMP-1, COMP-2, COMP-3, or DISPLAY usage and with a numeric integer value. If the data name is signed, the sign must be positive at the time the data name is used as a subscript.

A data name that is a subscript can also be subscripted; for example, A(B(C)). Note that for efficiency your subscripts should be S9(5) to S9(9) COMP.

The sample subscripts and data names used in Table 4-2 refer to the table defined in Example 4-16.

Table 4-2 Subscripting with Data Names
Data Descriptions of Subscript Data Names Procedural Instructions
01 SUB1 PIC 99 USAGE DISPLAY. MOVE 2 TO SUB1.
01 SUB2 PIC S9(9) USAGE COMP. MOVE 11 TO SUB2.
01 SUB3 PIC S99. MOVE 3 TO SUB3.
  MOVE ITEM5(SUB1,SUB2,SUB3) TO I-FIELD5.

4.3.4 Subscripting with Indexes

The same rules apply for specifying indexes as for subscripts, except that the index must be named in the INDEXED BY phrase of the OCCURS clause.

You cannot access index items as normal data items; that is, you cannot use them, redefine them, or write them to a file. However, the SET statement can change their values, and relation tests can examine their values. The index integer you specify in the SET statement must be in the range of one to the integer value in the OCCURS clause. The sample MOVE statement shown in Example 4-17 moves the contents of the third element of A-GROUP to I-FIELD.

Example 4-17 Subscripting with Index Name Items

Table Description:
 
      01 A-TABLE. 
         03 A-GROUP OCCURS 5 TIMES 
            INDEXED BY IND-NAME. 
            05   ITEMC   PIC X  VALUE "C". 
            05   ITEMD   PIC X  VALUE "D". 
      01 I-FIELD     PIC X(5). 
 
Procedural Instructions:
 
      SET IND-NAME TO 3. 
      MOVE A-GROUP(IND-NAME) TO I-FIELD. 

Note

Compaq COBOL initializes the value of all indexes to 1. Initializing indexes is an extension to the ANSI COBOL standard. Users who write COBOL programs that must adhere to standard COBOL should not rely on this feature.

4.3.5 Relative Indexing

To perform relative indexing when referring to a table element, you follow the index name with a plus or minus sign and an integer literal. Although it is easy to use, relative indexing generates additional overhead each time a table element is referenced in this way. The run-time overhead for relative indexing of variable-length tables is significantly greater than that required for fixed-length tables. If any of the range checks reveals an out-of-range index value, program execution terminates, and an error message is issued. You can use the -check flag (on Tru64 UNIX systems) or the /CHECK qualifier (on OpenVMS systems) to check the range when you compile the program.

On Tru64 UNIX, see Chapter 1 or the cobol man page for more information about the -check flag. <>

On OpenVMS, invoke the online help facility for Compaq COBOL at the OpenVMS system prompt for more information about the /CHECK qualifier. <>

The following sample MOVE statement moves the fourth repetition of A-GROUP to I-FIELD:


SET IND-NAME TO 1. 
MOVE A-GROUP(IND-NAME + 3) TO I-FIELD. 

4.3.6 Index Data Items

Often a program requires that the value of an index be stored outside of that item. Compaq COBOL provides the index data item to fulfill this requirement.

Index data items are stored as longword COMP items and must be declared with a USAGE IS INDEX phrase in the item description. Index data items can be explicitly modified only with the SET statement.

4.3.7 Assigning Index Values Using the SET Statement

You can use the SET statement to assign values to indexes associated with tables to reference particular table elements. The following sections discuss the two relevant SET statement formats. (All six SET statement formats are shown in the Compaq COBOL Reference Manual.)

4.3.7.1 Assigning an Integer Index Value with a SET Statement

When you use the SET statement, the index is set to the value you specify. The most straightforward use of the SET statement is to set an index name to an integer literal value. This example assigns a value of 5 to IND-5:


SET IND-5 TO 5. 

You can also set an index name to an integer data item. For example:


SET INDEX-A TO COUNT-1. 

More than one index can be set with a single SET statement. For example:


SET TAB1-IND TAB2-IND TO 15. 

Table indexes specified in INDEXED BY phrases can be displayed by using the WITH CONVERSION option with the DISPLAY statement. Also, you can display, move, and manipulate the value of the table index with an index data item. You do this by setting an index data item to the present value of an index. You can, for example, set an index data item and then display its value as shown in the following example:


SET INDEX-ITEM TO TAB-IND. 
         . 
         . 
         . 
DISPLAY INDEX-ITEM WITH CONVERSION. 

4.3.7.2 Incrementing an Index Value with the SET Statement

You can use the SET statement with the UP BY/DOWN BY clause to arithmetically alter the value of a index. A numeric literal is added to (UP BY) or subtracted from (DOWN BY) a table index. For example:


SET TABLE-INDEX UP BY 12. 
 
SET TABLE-INDEX DOWN BY 5. 

4.3.8 Identifying Table Elements Using the SEARCH Statement

The SEARCH statement is used to search a table for an element that satisfies a known condition. The statement provides for sequential and binary searches, which are described in the following sections.

4.3.8.1 Implementing a Sequential Search

The SEARCH statement allows you to perform a sequential search of a table. The OCCURS clause of the table description entry must contain the INDEXED BY phrase. If more than one index is specified in the INDEXED BY phrase, the first index is the controlling index for the table search unless you specify otherwise in the SEARCH statement.

The search begins at the current index setting and progresses through the table, checking each element against the conditional expression. The index is incremented by 1 as each element is checked. If the conditional expression is true, the associated imperative statement executes; otherwise, program control passes to the next procedural sentence. This terminates the search, and the index points to the current table element that satisfied the conditional expression.

If no table element is found that satisfies the conditional expression, program control passes to the AT END exit path; otherwise, program control passes to the next procedural sentence.

You can use the optional VARYING phrase of the SEARCH statement by specifying any of the following:

Regardless of which method you use, the index specified in the INDEXED BY phrase of the table being searched is incremented. This controlling index, when compared against the allowable number of occurrences in the table, dictates the permissible search range. When the search terminates, either successfully or unsuccessfully, the index remains at its current setting. At this point, you can reference the data in the table element pointed to by the index, unless the AT END condition is true. If the AT END condition is true, and if the -check flag (on Tru64 UNIX systems) or the /CHECK qualifier (on OpenVMS systems) has been specified, the compiler issues a run-time error message indicating that the subscript is out of range.

When you vary an index associated with the table being searched, the index name can be any index you specify in the INDEXED BY phrase. It becomes the controlling index for the search and is the only index incremented. Example 4-18 and Example 4-20 show how to vary an index other than the first index.

When you vary an index data item or an integer data item, either the index data item or the integer data item is incremented. The first index name you specify in the INDEXED BY phrase of the table being searched becomes the controlling index and is also incremented. The index data item or the integer data item you vary does not function as an index; it merely allows you to maintain an additional pointer to elements within a table. Example 4-18 and Example 4-21 show how to vary an index data item or an integer data item.

When you vary an index associated with a table other than the one you are searching, the controlling index is the first index you specify in the INDEXED BY phrase of the table you are searching. Each time the controlling index is incremented, the index you specify in the VARYING phrase is incremented. In this manner, you can search two tables in synchronization. Example 4-18 and Example 4-22 show how to vary an index associated with a table other than the one you are searching.

When you omit the VARYING phrase, the first index you specify in the INDEXED BY phrase becomes the controlling index. Only this index is incremented during a serial search. Example 4-18 and Example 4-23 show how to perform a serial search without using the VARYING phrase.

4.3.8.2 Implementing a Binary Search

You can use the SEARCH statement to perform a nonsequential (binary) table search.

To perform a binary search, you must specify an index name in the INDEXED BY phrase and a search key in the KEY IS phrase of the OCCURS clause of the table being searched.

A binary search depends on the ASCENDING/DESCENDING KEY attributes. If you specify an ASCENDING KEY, the data in the table must either be stored in ascending order or sorted in ascending order prior to the search. For a DESCENDING KEY, data must be stored or sorted in descending order prior to the search.

On Alpha, you can sort an entire table in preparation for a binary search. Use the SORT statement (Format 2, a Compaq extension), described in the Compaq COBOL Reference Manual. <>

During a binary search, the first (or only) index you specify in the INDEXED BY phrase of the OCCURS clause of the table being searched is the controlling index. You do not have to initialize an index in a binary search because index manipulation is automatic.

In addition to being generally faster than a sequential search, a binary search allows multiple equality checks.

The following search sequence lists the capabilities of a binary search. At program execution time, the system:

  1. Examines the range of permissible index values, selects the median value, and assigns this value to the index.
  2. Checks for equality in WHEN and AND clauses.
  3. Terminates the search if all equality statements are true. If you use the imperative statement after the final equality clause, that statement executes; otherwise, program control passes to the next procedural sentence, the search exits, and the index retains its current value.
  4. Takes the following actions if the equality test of a table element is false:
    1. Executes the imperative statement associated with the AT END statement (if present) when all table elements have been tested. If there is no AT END statement, program control passes to the next procedural statement.
    2. Determines which half of the table is to be eliminated from further consideration. This is based on whether the key being tested was specified as ASCENDING or DESCENDING and whether the test failed because of a greater-than or less-than comparison. For example, if the key values are stored in ascending order, and the median table element being tested is greater than the value of the argument, then all key elements following the one being tested must also be greater. Therefore, the upper half of the table is removed from further consideration and the search continues at the median point of the lower half.
    3. Begins processing all over again at Step 1.

A useful variation of the binary search is that of specifying multiple search keys. Multiple search keys allow you to select a specified table element from among several elements that have duplicate low-order keys. An example is a telephone listing where several people have the same last and first names, but different middle initials. All specified keys must be either ascending or descending. Example 4-24 shows how to use multiple search keys.

The table in Example 4-18 is followed by several examples (Examples 4-19, 4-20, 4-21, 4-22, and 4-23) of how to search it.

Example 4-18 Sample Table

DATA DIVISION. 
WORKING-STORAGE SECTION. 
01  TEMP-IND                            USAGE IS INDEX. 
01  FED-TAX-TABLES. 
    02  ALLOWANCE-DATA. 
        03  FILLER                      PIC X(70) VALUE 
            "0101440 
-           "0202880 
-           "0304320 
-           "0405760 
-           "0507200 
-           "0608640 
-           "0710080 
-           "0811520 
-           "0912960 
-           "1014400". 
    02  ALLOWANCE-TABLE REDEFINES ALLOWANCE-DATA. 
        03  FED-ALLOWANCES OCCURS 10 TIMES 
            ASCENDING KEY IS ALLOWANCE-NUMBER 
            INDEXED BY IND-1. 
            04  ALLOWANCE-NUMBER        PIC XX. 
            04  ALLOWANCE               PIC 99999. 
 
    02 SINGLES-DEDUCTION-DATA. 
        03  FILLER                      PIC X(112) VALUE 
            "0250006700000016 
-           "0670011500067220 
-           "1150018300163223 
-           "1830024000319621 
-           "2400027900439326 
-           "2790034600540730 
-           "3460099999741736". 
   02   SINGLE-DEDUCTION-TABLE REDEFINES SINGLES-DEDUCTION-DATA. 
        03  SINGLES-TABLE OCCURS 7 TIMES 
            ASCENDING KEY IS S-MIN-RANGE S-MAX-RANGE 
            INDEXED BY IND-2, TEMP-INDEX. 
            04  S-MIN-RANGE             PIC 99999. 
            04  S-MAX-RANGE             PIC 99999. 
            04  S-TAX                   PIC 9999. 
            04  S-PERCENT               PIC V99. 
 
    02  MARRIED-DEDUCTION-DATA. 
        03  FILLER                      PIC X(119) VALUE 
            "04800096000000017 
-           "09600173000081620 
-           "17300264000235617 
-           "26400346000390325 
-           "34600433000595328 
-           "43300500000838932 
-           "50000999991053336". 
    02  MARRIED-DEDUCTION-TABLE REDEFINES MARRIED-DEDUCTION-DATA. 
        03 MARRIED-TABLE OCCURS 7 TIMES 
           ASCENDING KEY IS M-MIN-RANGE M-MAX-RANGE 
           INDEXED BY IND-0, IND-3. 
           04  M-MIN-RANGE              PIC 99999. 
           04  M-MAX-RANGE              PIC 99999. 
           04  M-TAX                    PIC 99999. 
           04  M-PERCENT                PIC V99. 

Example 4-19 shows how to perform a serial search.

Example 4-19 A Serial Search

01   TAXABLE-INCOME PIC 9(6) VALUE 50000. 
01   FED-TAX-DEDUCTION PIC 9(6). 
PROCEDURE DIVISION. 
BEGIN. 
       PERFORM SINGLE. 
       DISPLAY FED-TAX-DEDUCTION. 
       STOP RUN. 
SINGLE. 
       IF TAXABLE-INCOME < 02500 
               GO TO END-FED-COMP. 
       SET IND-2 TO 1. 
       SEARCH SINGLES-TABLE AT END 
               GO TO TABLE-2-ERROR 
          WHEN TAXABLE-INCOME = S-MIN-RANGE(IND-2) 
               MOVE S-TAX(IND-2) TO FED-TAX-DEDUCTION 
          WHEN TAXABLE-INCOME < S-MAX-RANGE(IND-2) 
               COMPUTE FED-TAX-DEDUCTION = 
                   S-TAX(IND-2) + (TAXABLE-INCOME - S-TAX(IND-2)) * 
                   S-PERCENT(IND-2). 
   .
   .
   .

Example 4-20 shows how to use SEARCH while varying an index other than the first index.

Example 4-20 Using SEARCH and Varying an Index Other than the First Index

01   TAXABLE-INCOME PIC 9(6) VALUE 50000. 
01   FED-TAX-DEDUCTION PIC 9(6). 
PROCEDURE DIVISION. 
BEGIN. 
       PERFORM MARRIED. 
       DISPLAY FED-TAX-DEDUCTION. 
       STOP RUN. 
MARRIED. 
       IF TAXABLE-INCOME < 04800 
               MOVE ZEROS TO FED-TAX-DEDUCTION 
               GO TO END-FED-COMP. 
       SET IND-3 TO 1. 
       SEARCH MARRIED-TABLE VARYING IND-3 AT END 
               GO TO TABLE-3-ERROR 
          WHEN TAXABLE-INCOME = M-MIN-RANGE(IND-3) 
               MOVE M-TAX(IND-3) TO FED-TAX-DEDUCTION 
          WHEN TAXABLE-INCOME < M-MAX-RANGE(IND-3) 
               COMPUTE FED-TAX-DEDUCTION = 
                   M-TAX(IND-3) + (TAXABLE-INCOME - M-TAX(IND-3)) * 
                   M-PERCENT(IND-3). 
   .
   .
   .

Example 4-21 shows how to use SEARCH while varying an index data item.

Example 4-21 Using SEARCH and Varying an Index Data Item

01   TAXABLE-INCOME PIC 9(6) VALUE 50000. 
01   FED-TAX-DEDUCTION PIC 9(6). 
PROCEDURE DIVISION. 
BEGIN. 
       PERFORM SINGLE. 
       DISPLAY FED-TAX-DEDUCTION. 
       STOP RUN. 
SINGLE. 
       IF TAXABLE-INCOME < 02500 
               GO TO END-FED-COMP. 
       SET IND-2 TO 1. 
       SEARCH SINGLES-TABLE VARYING TEMP-IND AT END 
               GO TO TABLE-2-ERROR 
          WHEN TAXABLE-INCOME = S-MIN-RANGE(IND-2) 
               MOVE S-TAX(IND-2) TO FED-TAX-DEDUCTION 
          WHEN TAXABLE-INCOME < S-MAX-RANGE(IND-2) 
               MOVE S-TAX(IND-2) TO FED-TAX-DEDUCTION 
               SUBTRACT S-MIN-RANGE(IND-2) FROM TAXABLE-INCOME 
               MULTIPLY TAXABLE-INCOME BY S-PERCENT(IND-2) ROUNDED 
               ADD TAXABLE-INCOME TO FED-TAX-DEDUCTION. 
   .
   .
   .

Example 4-22 shows how to use SEARCH while varying an index not associated with the target table.

Example 4-22 Using SEARCH and Varying an Index not Associated with the Target Table

01   TAXABLE-INCOME PIC 9(6) VALUE 50000. 
01   FED-TAX-DEDUCTION PIC 9(6). 
PROCEDURE DIVISION. 
BEGIN. 
       PERFORM SINGLE. 
       DISPLAY FED-TAX-DEDUCTION. 
       STOP RUN. 
SINGLE. 
        IF TAXABLE-INCOME < 02500 
               GO TO END-FED-COMP. 
        SET IND-2 TO 1. 
        SEARCH SINGLES-TABLE VARYING IND-0 AT END 
               GO TO TABLE-2-ERROR 
          WHEN TAXABLE-INCOME = S-MIN-RANGE(IND-2) 
               MOVE S-TAX(IND-2) TO FED-TAX-DEDUCTION 
 
          WHEN TAXABLE-INCOME < S-MAX-RANGE(IND-2) 
               MOVE S-TAX(IND-2) TO FED-TAX-DEDUCTION 
               SUBTRACT S-MIN-RANGE(IND-2) FROM TAXABLE-INCOME 
               MULTIPLY TAXABLE-INCOME BY S-PERCENT(IND-2) ROUNDED 
               ADD TAXABLE-INCOME TO FED-TAX-DEDUCTION. 
   .
   .
   .

Example 4-23 shows how to perform a serial search without using the VARYING phrase.

Example 4-23 Doing a Serial Search Without Using the VARYING Phrase

01   NR-DEPENDENTS     PIC 9(2)  VALUE 3. 
01   GROSS-WAGE        PIC 9(6)  VALUE 50000. 
01   TAXABLE-INCOME    PIC 9(6)  VALUE 50000. 
01   FED-TAX-DEDUCTION PIC9(6). 
01   MARITAL-STATUS    PIC X     VALUE "M". 
PROCEDURE DIVISION. 
BEGIN. 
       PERFORM FED-DEDUCT-COMPUTATION. 
       DISPLAY TAXABLE-INCOME. 
       STOP RUN. 
FED-DEDUCT-COMPUTATION. 
          SET IND-1 TO 1. 
          SEARCH FED-ALLOWANCES AT END 
                 GO TO TABLE-1-ERROR 
            WHEN ALLOWANCE-NUMBER(IND-1) = NR-DEPENDENTS 
                 SUBTRACT ALLOWANCE(IND-1) FROM GROSS-WAGE 
                     GIVING TAXABLE-INCOME ROUNDED. 
          IF MARITAL-STATUS = "M" 
                 GO TO MARRIED. 
MARRIED. 
   .
   .
   .

Example 4-24 shows how to perform a multiple-key, binary search.

Example 4-24 A Multiple-Key, Binary Search

IDENTIFICATION DIVISION. 
PROGRAM-ID. MULTI-KEY-SEARCH. 
DATA DIVISION. 
WORKING-STORAGE SECTION. 
01 DIRECTORY-TABLE. 
   05 NAMES-NUMBERS. 
      10 FILLER                PIC X(30) 
         VALUE "SMILEY    HAPPY     T.213-4332". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     ALAN      C.881-4987". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     CHARLES   J.345-2398". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     FREDERICK   745-0223". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     HARRY     C.573-3306". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     HARRY     J.295-3485". 
      10 FILLER                PIC X(30) 
         VALUE "SMITH     LARRY     X.976-5504". 
      10 FILLER                PIC X(30) 
         VALUE "SMITHWOOD ALBERT    J.349-9927". 
   05 PHONE-DIRECTORY-TABLE REDEFINES NAMES-NUMBERS OCCURS 8 TIMES 
                                  ASCENDING KEY IS LAST-NAME 
                                                   FIRST-NAME 
                                                   MID-INIT 
                                  INDEXED BY DIR-INDX. 
         15 LAST-NAME          PIC X(10). 
         15 FIRST-NAME         PIC X(10). 
         15 MID-INIT           PIC XX. 
         15  PHONE-NUM         PIC X(8). 
PROCEDURE DIVISION. 
MULTI-KEY-BINARY-SEARCH. 
    SEARCH ALL PHONE-DIRECTORY-TABLE 
           WHEN LAST-NAME(DIR-INDX) = "SMITH" 
           AND FIRST-NAME(DIR-INDX) = "HARRY" 
           AND MID-INIT(DIR-INDX) = "J." 
               NEXT SENTENCE. 
DISPLAY-RESULTS. 
    DISPLAY LAST-NAME(DIR-INDX)"," 
            FIRST-NAME(DIR-INDX) 
            MID-INIT(DIR-INDX) " " 
            PHONE-NUM(DIR-INDX). 


Previous Next Contents Index