HP 3000 Manuals

Sequential Table Processing [ ALLBASE/SQL COBOL Application Programming Guide ] MPE/iX 5.0 Documentation


ALLBASE/SQL COBOL Application Programming Guide

Sequential Table Processing 

In sequential table processing, you process an active set by fetching a
row at a time and optionally deleting or updating it.  Sequential table
processing is useful when the likelihood of row changes throughout a set
of rows is high and when a program user does not need to review multiple
rows to decide whether to change a specific row.

In the following example, rows for parts having the same SALESPRICE are
displayed one at a time.  The program user can delete a displayed row or
change its SALESPRICE. Note that the host variable declarations are
identical to those for the simple data manipulation example, since only
one row at a time is fetched.  Rows are fetched as long as SQLCODE is not
equal to 100:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
     01  PARTNUMBER            PIC X(16).
     01  PARTNAME              PIC X(30).
     01  PARTNAMEIND           SQLIND.
     01  SALESPRICE            PIC S9(8)V99 COMP-3.
     01  SALESPRICEIND         SQLIND.
     EXEC SQL END DECLARE SECTION END-EXEC.
     01  OK                    PIC S9(9) COMP VALUE   0.
     01  NOTFOUND              PIC S9(9) COMP VALUE 100.
     .
     .
     .
     PROCEDURE DIVISION.

         The cursor declared allows the user to change 
         the SALESPRICE of the current row.  It can also 
         be used to delete the current row. 

         EXEC SQL DECLARE PRICECURSOR
                   CURSOR FOR
                   SELECT PARTNUMBER, PARTNAME, SALESPRICE
                     FROM PURCHDB.PARTS
                    WHERE SALESPRICE = :SALESPRICE
               FOR UPDATE OF SALESPRICE
         END-EXEC.
         .
         .  The program accepts a salesprice value 
         .  from the user. 
         .
         EXEC SQL OPEN PRICECURSOR END-EXEC.
         IF SQLCODE = OK
            PERFORM DISPLAY-ROW THRU DISPLAY-ROW-EXIT
            UNTIL SQLCODE = NOTFOUND
         ELSE
         IF SQLCODE = NOTFOUND
            DISPLAY "No rows have the salesprice specified!"
         ELSE
            PERFORM SQL-STATUS-CHECK.

     DISPLAY-ROW.
         EXEC SQL FETCH  PRICECURSOR
                   INTO :PARTNUMBER,
                        :PARTNAME PARTNAMEIND,
                        :SALESPRICE SALESPRICEIND
         END-EXEC.
         .
         .       If all rows have not been fetched, the next 
         .       row in the active set is displayed.  Depending on 
         .       the user's response to a program prompt, the row may 
         .       be deleted or its SALESPRICE value changed. 
         .
         IF RESPONSE = '/'
            GO TO DISPLAY-ROW-EXIT
         ELSE
         IF RESPONSE = 'D'
            EXEC SQL DELETE FROM PURCHDB.PARTS
                      WHERE CURRENT OF PRICECURSOR
            END-EXEC
         .
         .       Status checking code appears here. 
         .
         ELSE
         IF RESPONSE = 'U'
         .
         .        A new SALESPRICE is accepted. 
         .
            EXEC SQL UPDATE PURCHDB.PARTS
                        SET SALESPRICE = :SALESPRICE
                      WHERE CURRENT OF PRICECURSOR
            END-EXEC
          .
          .       Status checking code appears here. 
          .
     DISPLAY-ROW-EXIT.

Sequential table processing is discussed in more detail in Chapter 8.



MPE/iX 5.0 Documentation