HP 3000 Manuals

Comparing a Procedure and an Embedded SQL Application [ ALLBASE/SQL Release F.0 Application Programming Bulletin for MPE/iX ] MPE/iX 5.0 Documentation


ALLBASE/SQL Release F.0 Application Programming Bulletin for MPE/iX

Comparing a Procedure and an Embedded SQL Application 

Imagine a data entry application which either updates prices or adds new
parts to the Parts table in the sample DBEnvironment PartsDBE depending
on whether the Part number is currently in the table.  You could code
this application using conventional embedded SQL programming.  In that
approach, you would declare host variables, then prompt for data, then
access the database:

     In C:                                   In COBOL:

     EXEC SQL BEGIN DECLARE SECTION;     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
     char  PartNumber[17];               01  PARTNUMBER    PIC X(16).
     float SalesPrice;                   01  SALESPRICE    PIC S9(8)V9(2) COMP-3.
     sqlind SalesPriceInd;               01  SALESPRICEIND SQLIND.
     float InputPrice;                   01  INPUTPRICE    PIC S9(8)V9(2) COMP-3.
     EXEC SQL END DECLARE SECTION;       EXEC SQL END DECLARE SECTION END-EXEC.
     Prompt for values for part number and input salesprice,
     then test for the existence of the part number in the Parts table. 

     In C:                                  In COBOL:

     EXEC SQL SELECT SalesPrice INTO     EXEC SQL SELECT SALESPRICE INTO
     :SalesPrice :SalesPriceInd          :SALESPRICE :SALESPRICEIND
     FROM PurchDB.Parts                  FROM PURCHDB.PARTS
     WHERE PartNumber = :PartNumber;     WHERE PARTNUMBER = :PARTNUMBER END-EXEC.

     If the part number is in the table, update the price. 

     In C:                                  In COBOL:

     if (sqlcode == 0) {                 IF SQLCODE IS ZERO THEN
        EXEC SQL UPDATE PurchDB.Parts       EXEC SQL UPDATE PurchDB.Parts
        SET SalesPrice = :InputPrice        SET SalesPrice = :InputPrice
        WHERE PartNumber = :PartNumber;     WHERE PartNumber = :PARTNUMBER END-EXEC.
        if(sqlcode != 0)                    IF SQLCODE IS NOT ZERO THEN
           printf("Error on UPDATE\n");        DISPLAY "ERROR ON UPDATE."
       }                                    END-IF
                                         END-IF.

     If the part number is not in the table, add it. 

     In C:                                  In COBOL:

     elseif (sqlcode == 100) {           IF SQLCODE IS 100 THEN
        EXEC SQL INSERT INTO                EXEC SQL INSERT INTO
        PurchDB.Parts (PartNumber,            PURCHDB.PARTS (PARTNUMBER,SALESPRICE)
        SalesPrice) VALUES                    VALUES (:PARTNUMBER,:INPUTPRICE)
        (:PartNumber, :InputPrice);         END-EXEC.
        if(sqlcode != 0)                    IF SQLCODE IS NOT ZERO THEN
          printf("Error on INSERT\n");         DISPLAY "ERROR ON INSERT."
        }                                   END-IF
                                         END-IF.

As an alternative, you could code all this in a procedure, then call the
procedure from your application.  Here is the CREATE PROCEDURE statement:

     CREATE PROCEDURE NewPrice(PartNumber CHAR(16) NOT NULL,
                               InputPrice DECIMAL(10,2) NOT NULL) AS
     BEGIN
        SELECT PartNumber INTO :PartNumber FROM
        PurchDB.Parts WHERE PartNumber = :PartNumber;

        if ::sqlcode = 0 then /* Row was found, so price is updated */
                 UPDATE PurchDB.Parts SET SalesPrice = :InputPrice
                    WHERE PartNumber = :PartNumber;
                 if ::sqlcode <> 0 then
                     print 'Error occurred during UPDATE';
                 endif;
        elseif ::sqlcode= 100 then  /* Row not found, so insert it */
                 INSERT INTO PurchDB.Parts (PartNumber, SalesPrice)
                      VALUES (:PartNumber, :InputPrice);
                 if ::sqlcode <> 0 then
                     print 'Error occurred during INSERT';
                 endif;
        else
           print 'Error occurred during SELECT';

        endif;
        return ::sqlcode;
     end;

The following is the code that would be required in your application to
execute the procedure:

     Declare host variables. 

     In C:                                  In COBOL:

     EXEC SQL BEGIN DECLARE SECTION       EXEC SQL BEGIN DECLARE SECTION END-EXEC.
     char  Number[17];                    01  NUMBER       PIC X(16).
     double Price;                        01  PRICE        PIC S9(8)V9(2) COMP-3.
     integer ReturnCode;                  01  RETCODE      PIC S9(4) COMP.
     EXEC SQL END DECLARE SECTION         EXEC SQL END DECLARE SECTION END-EXEC.

     Prompt for values for part number and input salesprice. 

     Call the procedure to process the entry. 

     In C:                                  In COBOL:

     EXEC SQL EXECUTE PROCEDURE           EXEC SQL EXECUTE PROCEDURE
        :ReturnCode =                        :RETCODE =
          NewPrice(:Number, :Price);            NEWPRICE (:NUMBER, :PRICE)
                                          END-EXEC.
     if(sqlca.sqlcode==0) {               IF SQLCODE IS ZERO THEN
       if(ReturnCode!=0)                      IF RETCODE IS NOT ZERO THEN
         printf("Error in NewPrice\n");           DISPLAY "ERROR IN NEWPRICE."
       }                                      END-IF
                                          END-IF.

The host variables may be passed as parameters, but host variables are
not available within the procedure.  You must define parameters to store
data that is passed into the procedure.  Parameters PartNumber and
SalesPrice are used within the procedure to store the data passed in from
the host variables :Number and :Price.  In this example, the two
variables are named differently so as to distinguish them.  However, you
could use the same names for the parameters as for the host variables,
since their scopes do not overlap.

Why Use a Procedure? 

The advantage of coding a procedure instead of a segment of application
code is that you can separate the programmatic function (entering a new
price) from the need to know the structure of the database itself.  Thus,
if the structure of the database should change, it is only necessary to
modify the procedure, not the application code.  If the procedure is used
by many different applications, the savings in application maintenance
can be considerable.



MPE/iX 5.0 Documentation