HP 3000 Manuals

Using the SQLCA [ ALLBASE/SQL COBOL Application Programming Guide ] MPE/iX 5.0 Documentation


ALLBASE/SQL COBOL Application Programming Guide

Using the SQLCA 

The SQL communications area is known as the SQLCA. Every ALLBASE/SQL
COBOL program must declare the SQLCA by putting the INCLUDE SQLCA
statement somewhere in the WORKING-STORAGE SECTION or the LINKAGE
SECTION.

     WORKING-STORAGE SECTION.
     EXEC SQL INCLUDE SQLCA END-EXEC.

The COBOL preprocessor generates the following declaration in SQLOUT
after it parses this SQL command:

      WORKING STORAGE SECTION.

           **** Start SQL Preprocessor ****
           $INCLUDE SQLCONST
           $INCLUDE SQLVAR
           **** End SQL Preprocessor   ****

           **** Start SQL Preprocessor ****
           *EXEC SQL INCLUDE SQLCA END-EXEC.
           **** Start Inserted Statements ****
            01  SQLCA.
                05  SQLCAID       PIC X(8).
                05  SQLCABC       PIC S9(9) COMP SYNC.
                05  SQLCODE       PIC S9(9) COMP SYNC.   <--
                05  SQLERRM.
                    49  SQLERRML  PIC S9(9) COMP SYNC.
                    49  SQLERRMC  PIC X(256).
                05  SQLERRP       PIC X(8).
                05  SQLERRD       OCCURS 6 TIMES         <--SQLERRD(3)
                                  PIC S9(9) COMP SYNC.
                05  SQLWARN.
                    10  SQLWARN0  PIC X(1).              <--
                    10  SQLWARN1  PIC X(1).              <--
                    10  SQLWARN2  PIC X(1).              <--
                    10  SQLWARN3  PIC X(1).
                    10  SQLWARN4  PIC X(1).
                    10  SQLWARN5  PIC X(1).
                    10  SQLWARN6  PIC X(1).              <--
                    10  SQLWARN7  PIC X(1).
                05  SQLEXT1       PIC X(4).
                05  SQLEXT2       PIC X(4).
           **** End SQL Preprocessor   ****

The data items identified by an arrow are for you to use in status
checking.  The other fields are reserved for use by ALLBASE/SQL only.

You may want to place the SQLCA declaration first in the WORKING-STORAGE
SECTION. That way, if you compile the program with range checking off,
this vital data structure will not be inadvertently overwritten by array
references beyond the limit of a previously declared array.

As discussed in the previous chapter "Host Variables," the SQLCA must be
passed whenever you call a subprogram that executes SQL commands in the
same DBEnvironment. 

The following table gives an overview of how ALLBASE/SQL sets these
fields.  Each field is then described with brief examples of how you can
use it, including examples for using SQLEXPLAIN. Methods of handling
specific status checking tasks are found in the succeeding section,
"Approaches to Status Checking." 

          Table 5-1.  SQLCA Status Checking Fields 

--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
|          FIELD NAME          |          SET TO          |              CONDITION               |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLCODE                      |            0             | no error occurred durring command    |
|                              |                          | execution                            |
|                              |       less than 0        |                                      |
|                              |                          | error, command not executed          |
|                              |           100            |                                      |
|                              |                          | no rows qualify for DML operation    |
|                              |                          | (does not apply to dynamic commands) |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLERRD(3)                   | number of rows put into  | data retrieval operation             |
|                              |  output host variables   |                                      |
|                              |                          | data change operation                |
|                              | number of rows processed |                                      |
|                              |                          | error in single row data change      |
|                              |            0             | operation                            |
|                              |                          |                                      |
|                              |            0             | SQLCODE equals 100                   |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLWARN0                     |            W             | warning, command not properly        |
|                              |                          | executed                             |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLWARN1                     |            W             | at least one character string value  |
|                              |                          | was truncated when being stored in a |
|                              |                          | host variable                        |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLWARN2                     |            W             | at least one null value was          |
|                              |                          | eliminated from the argument set of  |
|                              |                          | an aggregate function                |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------
|                              |                          |                                      |
| SQLWARN6                     |            W             | the current transaction was rolled   |
|                              |                          | back                                 |
|                              |                          |                                      |
--------------------------------------------------------------------------------------------------

SQLCODE 

SQLCODE can contain one of the following values:

   *   0, when an SQL command executes without generating an error
       condition and without generating a no rows qualify condition.

   *   A negative number, when an error condition exists and an
       ALLBASE/SQL command cannot be executed.

   *   100, when no rows qualify for one of the following commands, but
       no error condition exists:

            SELECT
            INSERT
            UPDATE (non-dynamic execution only)
            DELETE (non-dynamic execution only)
            BULK SELECT
            FETCH
            BULK FETCH
            UPDATE WHERE CURRENT
            DELETE WHERE CURRENT

Note that the absolute value of SQLCODE is the same as the absolute value
associated with its corresponding message in the ALLBASE/SQL message
catalog.  This absolute value is part of the returned message.  If an
error occurs, the message number is preceded by DBERR. For example, the
error message associated with an SQLCODE of -2613 is:

     Precision digits lost in decimal operation MULTIPLY.  (DBERR 2613)

SQLCODE is set by all SQL commands except the following directives:

     BEGIN DECLARE SECTION
     DECLARE
     END DECLARE SECTION
     INCLUDE
     WHENEVER

When SQLCODE is -4008, -14024, or a greater negative value than -14024,
ALLBASE/SQL automatically rolls back the current transaction.  When this
condition occurs, ALLBASE/SQL also sets SQLWARN6 to W. Refer to the
discussion later in this chapter on SQLWARN6 for more on this topic.

More than one SQLCODE is returned when more than one error occurs.  For
example, if you attempt to execute the following SQL command, two
negative SQLCODE values result:

     EXEC SQL ADD PUBLIC, GROUP1 TO GROUP GROUP1 END-EXEC.

The SQLCODEs associated with the two errors are:

     -2308, which indicates the reserved name PUBLIC is invalid.
     -2318, which indicates you cannot add a group to itself.

To obtain all SQLCODEs associated with the execution of an SQL command,
you execute the SQLEXPLAIN command until SQLCODE is 0:

        IF SQLCODE IS EQUAL TO 100
            DISPLAY "No rows qualified for this operation."
        IF SQLCODE IS LESS THAN ZERO
            PERFORM SQL-STATUS-CHECK
            UNTIL SQLCODE IS ZERO.

     SQL-STATUS-CHECK.
        EXEC SQL SQLEXPLAIN :SQLMESSAGE END-EXEC.

The paragraph named SQL-STATUS-CHECK is executed when SQLCODE is a
negative number.  Before executing SQLEXPLAIN for the first time, the
program has access to the first SQLCODE returned.  Each time SQLEXPLAIN
is executed subsequently, the next SQLCODE becomes available to the
program, and so on until SQLCODE equals 0.

This example explicitly tests the value of SQLCODE twice:  first to
determine whether it is equal to 100, then to determine whether it is
less than 0.  If the value 100 exists, no error will have occurred and
the program will display the message No rows qualify for this operation.

It is necessary for the program to display its own message in this case,
because SQLEXPLAIN messages are available to your program only when
SQLCODE contains a negative number or when SQLWARN0 contains a W.

The SQLCODE is also used in implicit status checking:

   *   ALLBASE/SQL tests for the condition SQLCODE less than 0 when you
       use the SQLERROR option of the WHENEVER command.

   *   ALLBASE/SQL tests for the condition SQLCODE equal to 100 when you
       use the NOT FOUND option of the WHENEVER command.

In the following situation, when ALLBASE/SQL detects a negative SQLCODE,
the paragraph named GET-SQLCODE is executed.  When ALLBASE/SQL detects an
SQLCODE of 100, the paragraph named NOT-FOUND is executed instead: 

     EXEC SQL WHENEVER SQLERROR GO TO GET-SQLCODE END-EXEC.
     EXEC SQL WHENEVER NOT FOUND GO TO NOT-FOUND END-EXEC.

WHENEVER commands remain in effect for all SQL commands that appear
physically after them in the source program until another WHENEVER
command for the same condition appears.

The scope of WHENEVER commands is fully explained later in this chapter
under "Implicit Status Checking Techniques."

SQLERRD(3) 

SQLERRD(3) can contain one of the following values:

   *   0, when SQLCODE is 100 or when one of the following commands
       causes an error condition:

            INSERT
            UPDATE
            DELETE
            UPDATE WHERE CURRENT
            DELETE WHERE CURRENT

       If an error occurs during execution of INSERT, UPDATE, or DELETE,
       one or more rows may have been processed prior to the error.  In
       these cases, you may want to either COMMIT WORK or ROLLBACK WORK,
       depending on the transaction.  For example, if all or no rows
       should be updated for logical data consistency, use ROLLBACK WORK.
       However, if logical data consistency is not an issue, COMMIT WORK
       may minimize re-processing time.

   *   A positive number, when SQLCODE is 0.  In this case, the positive
       number provides information about the number of rows processed in
       the following data manipulation commands.

       The number of rows inserted, updated, or deleted in one of the
       following operations:

            INSERT
            UPDATE
            DELETE

            UPDATE WHERE CURRENT
            DELETE WHERE CURRENT

       The number of rows put into output host variables when one of the
       following commands is executed:

            SELECT
            BULK SELECT
            FETCH
            BULK FETCH

   *   A positive number, when SQLCODE is less than 0.  In this case,
       SQLERRD(3) indicates the number of rows that were successfully
       retrieved or inserted prior to the error condition:

            BULK SELECT
            BULK FETCH
            BULK INSERT

       As in the case of INSERT, UPDATE, and DELETE, mentioned above, you
       can use either a COMMIT WORK or ROLLBACK WORK command, as
       appropriate.

SQLWARN0 

A W in SQLWARN0, in conjunction with a 0 in SQLCODE, indicates that the
SQL command just executed caused a warning condition.

Warning conditions flag unusual but not necessarily important conditions.
For example, if a program attempts to submit an SQL command that grants
an already existing authority, a message such as the following would be
retrieved when SQLEXPLAIN is executed:

     User JOANN@GRAY already has DBA authorization.  (DBWARN 2006)

In the case of the following warning, the situation may or may not
indicate a problem:

     A transaction in progress was aborted.  (DBWARN 2010)

This warning occurs when a program submits a RELEASE command without
first terminating a transaction with a COMMIT WORK or ROLLBACK WORK. If
the transaction did not perform any UPDATE, INSERT, or DELETE operations,
this situation will not cause work to be lost.  If the transaction did 
perform UPDATE, INSERT, or DELETE operations, the database changes are
rolled back when the RELEASE command is processed. 

You retrieve the appropriate warning message by using SQLEXPLAIN. Note
that you cannot explicitly test SQLWARN0 the way you can test SQLCODE,
since SQLWARN0 always contains W when a warning occurs.

An error and a warning condition may exist at the same time.  In this
event, SQLCODE is set to a negative number, and SQLWARN0 is set to W.
Messages describing all the warnings and errors can be displayed as
follows:

        IF SQLCODE IS NOT ZERO
        PERFORM DISPLAY-MESSAGE UNTIL SQLCODE IS ZERO.

     DISPLAY-MESSAGE.
        EXEC SQL SQLEXPLAIN ;SQLMESSAGE END-EXEC.
        DISPLAY SQLMESSAGE.

If multiple warnings but no errors result when ALLBASE/SQL processes a
command, SQLWARN0 is set to W and remains set until the last warning
message has been retrieved by SQLEXPLAIN or another SQL command is
executed.  In the following example, DISPLAY-WARNINGS is executed when
this condition exists:

     IF SQLWARN0 IS "W" AND SQLCODE IS ZERO
         PERFORM DISPLAY-WARNINGS UNTIL SQLWARN0 IS NOT "W".

When you use the SQLWARNING option of the WHENEVER command, ALLBASE/SQL
checks for a W in SQLWARN0.  You can use the WHENEVER command to do
implicit status checking (equivalent to that done explicitly above) as
follows:

     EXEC SQL WHENEVER SQLWARNING GO TO DISPLAY-WARNINGS END-EXEC.
     EXEC SQL WHENEVER SQLERROR GO TO DISPLAY-MESSAGE END-EXEC.

SQLWARN1 

A W in SQLWARN1 indicates truncation of at least one character string
value when the string was stored in a host variable.  Any associated
indicator variable is set to the value of the string length before
truncation.

For example:

     EXEC SQL SELECT  PartNumber,
                      PartName
                INTO :PartNumber
                     :PartName :PartNameInd
                FROM  PurchDB.Parts
               WHERE  PartNumber = :PartNumber;

If PartName was declared as a character array of 20 bytes, and the
PartName column in the PurchDB.Parts table has a length of 30 bytes,
then:

   *   SQLWARN1 is set to W

   *   PartNameInd is set to 30 (the length of PartName in the table)

   *   SQLCODE is set to 0

   *   SQLEXPLAIN retrieves the message:

            Character string truncation during storage in host variable.
            (DBWARN 2040)

SQLWARN2 

A W in SQLWARN2 indicates that at least one null value was eliminated
from the argument set of an aggregrate function.

For example:

     EXEC SQL SELECT  MAX(OrderQty)
                INTO :MaxOrderQty
                FROM  PurchDB.OrderItems;

If any OrderQty values are null:

   *   :SQLWARN2 is set to W

   *   SQLCODE is set to 0

   *   SQLEXPLAIN retrieves the message:

            NULL values eliminated from the argument of an aggregate
            paragraph.   (DBWARN 2041)

SQLWARN6 

When an error occurs that causes ALLBASE/SQL to roll back the current
transaction, SQLWARN6 is set to W. ALLBASE/SQL automatically rolls back
transactions when SQLCODE is equal to -4008, or equal to or less than
-14024.

When such errors occur, ALLBASE/SQL:

   *   Sets SQLWARN6 to W

   *   Sets SQLWARN0 to W

   *   Sets SQLCODE to a negative number

If you want to terminate your program any time ALLBASE/SQL has to roll
back the current transaction, you can just test SQLWARN6.

     IF SQLCODE  < 0
          IF SQLWARN6 = "W"
          PERFORM SQL-STATUS-CHECK UNTIL SQLCODE IS ZERO
          PERFORM TERMINATE-PROGRAM
     ELSE PERFORM SQL-STATUS-CHECK UNTIL SQLCODE IS ZERO.

In this example, the program executes the paragraph SQL-STATUS-CHECK when
an error occurs.  The program terminates whenever ALLBASE/SQL has rolled
back a transaction, but continues if an error has occurred but was not
serious enough to cause transaction roll back.



MPE/iX 5.0 Documentation