Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.38.1 SEARCH Statement (format 1)

000010 @OPTIONS MAIN 
000020*-----------------------------------------------------------------------
000030* The SEARCH statement (format 1) retrieves specific elements from
000035* tables.
000040*-----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE  SECTION.
000090 01 GET-GOODS     PIC X(15).
000100 01 GET-NUM       PIC 9(4) BINARY.
000110 01 TOTAL         PIC 9(4) BINARY VALUE ZERO.
000120 01 COUNTER       PIC 9(1).
000130 01 PRICE-ED      PIC $$$$$9.
000140 01 TOTAL-ED      PIC ZZZZZ9.
000150 CONSTANT         SECTION.
000160 01 GOODS-DATA.
000170    02            PIC X(15) VALUE "PRINTER".
000180    02            PIC 9(4)  VALUE 400.
000190    02            PIC X(15) VALUE "MODEM".
000200    02            PIC 9(4)  VALUE 80.
000210    02            PIC X(15) VALUE "HARD DISK".
000220    02            PIC 9(4)  VALUE 280.
000230    02            PIC X(15) VALUE "DESKTOP TYPE".
000240    02            PIC 9(4)  VALUE 1500.
000250    02            PIC X(15) VALUE "NOTEBOOK TYPE".
000260    02            PIC 9(4)  VALUE 2200.
000270*-----------------------------------------------------------------------
000280* An index name is specified for any table referenced by a SEARCH 
000285* statement.
000290*-----------------------------------------------------------------------
000300 01               REDEFINES GOODS-DATA.
000310   02 GOODS       OCCURS 5 TIMES INDEXED BY IX.
000320      03 NAME         PIC X(15).
000330      03 PRICE        PIC 9(4).
000340*-----------------------------------------------------------------------
000350 PROCEDURE        DIVISION.
000360     PERFORM TEST BEFORE
000370             VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 5
000380       MOVE PRICE(COUNTER) TO PRICE-ED
000390       DISPLAY COUNTER "." NAME(COUNTER) PRICE-ED
000400     END-PERFORM.
000410     DISPLAY " ".
000420     DISPLAY "What would you like to buy?  Goods name >>" WITH NO 
000425             ADVANCING.
000430     ACCEPT GET-GOODS FROM CONSOLE.
000440     DISPLAY "How many would you like?                >>" WITH NO 
000445             ADVANCING.
000450     ACCEPT GET-NUM.
000460*-----------------------------------------------------------------------
000470* The operation to be executed upon a successful search is coded in the  
000480* SEARCH statement.
000490* Because search is executed sequentially from the index, a value is set 
000500* for the index to indicate the search starting position.  In addition, 
000510* search is stopped when the search object is found.  The value of the 
000515* index is then set at that point.  As a result, a subsequent SEARCH 
000517* statement can be coded to continue searching from the last position
000518* where an item was found.
000520*-----------------------------------------------------------------------
000530     SET IX TO 1.
000540     SEARCH GOODS
000550       WHEN NAME(IX) = GET-GOODS
000560         MOVE PRICE(IX) TO TOTAL
000570     END-SEARCH.
000580*-----------------------------------------------------------------------
000590     DISPLAY " ".
000600     IF TOTAL NOT = ZERO THEN
000610       COMPUTE TOTAL = TOTAL * GET-NUM
000620       MOVE TOTAL TO TOTAL-ED
000630       DISPLAY "The total amount is " TOTAL-ED " Dollars."
000640     ELSE
000650       DISPLAY "The input data is incorrect."
000660     END-IF.
000670 END PROGRAM SAMPLE.