Approaches to Status Checking
You can use one or both of the following approaches to checking SQLCA
values:
* Implicit status checking. This approach utilizes the WHENEVER
command to check SQLWarn(0) or SQLCode values. This type of
status checking is most useful when control can be passed to one
predefined point in the program unit to handle warnings and
errors.
* Explicit status checking. This approach uses your own FORTRAN
statements to explicitly examine SQLWarn(0), SQLWarn(6), SQLCode,
or SQLErrd(3). This type of status checking is useful when you
want to test for specific SQLCA values before passing control to
one of several locations in the program.
Error and warning conditions detected by either type of status checking
can be conveyed to the program user in several ways:
* SQLEXPLAIN can be used one or more times after an SQL command is
processed to retrieve warning and error messages from the
ALLBASE/SQL message catalog. The ALLBASE/SQL message catalog has
messages for every negative SQLCode and for every condition that
sets SQLWarn(0).
* Your own messages can be displayed when a certain condition
occurs.
* No message may be displayed, as when a condition exists that is
irrelevant to the program user.
This section illustrates various ways to use explicit and implicit status
checking and notify program users of the results of status checking.
Implicit Status Checking
The WHENEVER command consists of two components: a condition and an
action:
EXEC SQL WHENEVER Condition Action
There are three conditions:
* SQLERROR. If WHENEVER SQLERROR is in effect, ALLBASE/SQL checks
for the existence of a negative SQLCode after processing any SQL
command except:
BEGIN DECLARE SECTION INCLUDE
DECLARE CURSOR SQLEXPLAIN
END DECLARE SECTION WHENEVER
* SQLWARNING. If WHENEVER SQLWARNING is in effect, ALLBASE/SQL
checks for the existence of a W in SQLWarn(0) after processing any
SQL command except:
BEGIN DECLARE SECTION INCLUDE
DECLARE CURSOR SQLEXPLAIN
END DECLARE SECTION WHENEVER
* NOT FOUND. If WHENEVER NOT FOUND is in effect, ALLBASE/SQL checks
for the value 100 in SQLCode after processing a SELECT or FETCH
command.
A WHENEVER command for each of these conditions can be in effect at the
same time.
There are also three actions:
* STOP. If WHENEVER Condition STOP is in effect, ALLBASE/SQL rolls
back the current transaction and terminates the DBE session and
the program is terminated when the Condition exists.
* CONTINUE. If WHENEVER Condition CONTINUE is in effect, program
execution continues when the Condition exists. Any earlier
WHENEVER command for the same condition is cancelled.
* GOTO Label. If WHENEVER Condition GOTO Label is in effect, the
code routine located at that numeric label is executed when the
Condition exists. The label must appear in the same program unit
where the condition exists. GOTO and GO TO forms of this action
have exactly the same effect.
Any of these three actions may be specified for any of these three
conditions.
The WHENEVER command causes the FORTRAN preprocessor to generate
status-checking and status-handling code for each SQL command that comes
after it sequentially in the program. In the following program sequence,
for example, the WHENEVER command in SubprogramUnit1 is in effect for
SQLCOMMAND1, but not for SQLCOMMAND2, even though SQLCOMMAND1 is executed
first at runtime:
.
.
CALL SubprogramUnit1
CALL SubprogramUnit2
.
.
SUBROUTINE SubprogramUnit2
.
.
EXEC SQL SQLCOMMAND2
.
.
RETURN
END
SUBROUTINE SubprogramUnit1
.
.
EXEC SQL WHENEVER SQLERROR GOTO 2000
EXEC SQL WHENEVER SQLWARNING GOTO 3000
EXEC SQL WHENEVER NOT FOUND GOTO 4000
.
.
EXEC SQL SQLCOMMAND1
.
.
2000 CALL ErrorHandler
.
3000 CALL WarningHandler
.
4000 CALL NotFoundHandler
.
.
EXEC SQL WHENEVER SQLERROR CONTINUE
EXEC SQL WHENEVER SQLWARNING CONTINUE
EXEC SQL WHENEVER NOT FOUND CONTINUE
RETURN
END
The code generated reflects the condition and action in a WHENEVER
command. In the example above, the preprocessor inserts both a test for
a negative value in SQLCode, an SQLCode value equal to 100, and an
SQLWarn(0) value equal to W, and a statement that invokes the error
handling code routines located at Labels 2000, 3000, and 4000
respectfully:
SUBROUTINE SubprogramUnit1
.
.
C**** Start SQL Preprocessor ****
C EXEC SQL WHENEVER SQLERROR GOTO 2000
C EXEC SQL WHENEVER SQLWARNING GOTO 3000
C EXEC SQL WHENEVER NOT FOUND GOTO 4000
C**** Start Inserted Statements ****
C**** End SQL Preprocessor ****
.
.
C **** Start SQL Preprocessor ***
C EXEC SQL SQLCOMMAND1
C **** Start Inserted Statements ****
IF (SQLCODE .EQ. 0) THEN
CALL SQLXCO(SQLCAID,Statements for executing
1 SQLCOMMAND1 appear here)
IF (SQLWARN(0) .EQ. 'W') THEN
GO TO 3000
END IF
ELSE IF (SQLCODE .EQ. 100) THEN
GO TO 4000
ELSE IF (SQLCODE .LT. 0) THEN
GO TO 2000
END IF
C **** End SQL Preprocessor ****
.
.
2000 CALL ErrorHandler
.
3000 CALL WarningHandler
.
4000 CALL NotFoundHandler
.
.
C**** Start SQL Preprocessor ****
C EXEC SQL WHENEVER SQLERROR CONTINUE
C**** Start Inserted Statements ****
C**** End SQL Preprocessor ****
C**** Start SQL Preprocessor ****
C EXEC SQL WHENEVER SQLWARNING CONTINUE
C**** Start Inserted Statements ****
C**** End SQL Preprocessor ****
C**** Start SQL Preprocessor ****
C EXEC SQL WHENEVER NOT FOUND CONTINUE
C**** Start Inserted Statements ****
C**** End SQL Preprocessor ****
RETURN
END
As this example illustrates, you can pass control with a WHENEVER command
to an exception-handling code routine within the same program unit where
the error condition occurred. Because you use a GOTO statement rather
than a CALL statement, after the exception-handling subprogram unit is
executed, control cannot automatically return to the statement which
caused the error to occur. You must use another GOTO or a CALL statement
to explicitly pass control to a specific point in your program:
SUBROUTINE ErrorHandler
.
.
IF (SQLCode .LT. -14024) THEN
CALL TerminateProgram
ELSE
DO WHILE (SQLCode .NE. 0)
EXEC SQL SQLEXPLAIN :SQLMessage
CALL WriteOut (SQLMessage)
END DO
CALL BeginningOfProgram
C (* CALL Restart/Reentry point of program *)
ENDIF
.
.
RETURN
END
This exception-handling subprogram unit explicitly checks the first
SQLCode returned. The program terminates or it continues from the
Restart/Reentry point after all warning and error messages are displayed.
Note that a CALL statement had to be used in this code routine in order
to allow the program to transfer control to a specific point. A GOTO
statement transfers control only to another point in the same subprogram
unit and a RETURN statement returns control to the point in the program
where the error handling subprogram unit was called. Using a CALL
statement may be impractical when you want execution to continue from
different places in the program, depending on the part of the program
that provoked the error. How to handle this case is discussed under
"Explicit Status Checking" later in this chapter.
The FORTRAN preprocessor generates status-checking and status-handling
code for each SQL command that comes after a WHENEVER statement in the
source code until another WHENEVER statement is found. If the WHENEVER
statement includes a GOTO, there must be a corresponding label in each
subsequent subprogram unit following the WHENEVER statement that includes
SQL commands, or until another WHENEVER statement is encountered. It is
recommended that a WHENEVER condition CONTINUE statement be included at
the end of each subprogram unit that contains a WHENEVER condition GOTO
statement to eliminate the possibility of having an unresolved external
error at compile time.
Implicitly Invoking Status-Checking Subprogram Units.
The program illustrated in Figure 5-1 contains five WHENEVER commands:
* The WHENEVER command numbered 1 handles errors associated with the
following commands:
CONNECT
BEGIN WORK
COMMIT WORK
* The WHENEVER command numbered 2 turns off the previous WHENEVER
command.
* The WHENEVER commands numbered 3 through 5 handle warnings and
errors associated with the SELECT command.
* The WHENEVER commands numbered 6 turns off the previous WHENEVER
commands.
The code routine located at Label 1000 is executed when an error occurs
during the processing of session-related and transaction-related
commands. The program terminates after displaying all available error
messages. If a warning condition occurs during the execution of these
commands, the warning condition is ignored, because the WHENEVER
SQLWARNING CONTINUE command is in effect by default.
The code routine located at Label 2000 is executed when an error occurs
during the processing of the SELECT command. This code routine
explicitly examines the SQLCode value to determine whether it is -10002,
in which case it displays a warning message. If SQLCode contains another
value, subprogram unit SQLStatusCheck is executed. SQLStatusCheck
explicitly examines SQLCode to determine whether a deadlock or shared
memory problem occurred (SQLCode = -14024 or -4008 respectively) or
whether the error was serious enough to warrant terminating the program
(SQLCode < -14024).
* If a deadlock or shared memory problem occurred, the program
attempts to execute the SelectQuery subprogram unit starting at
Label 1001 as many as three times before notifying the user of the
deadlock or shared memory condition and terminating the program.
* If SQLCode contains a value less than -14024, the program
terminates after all available warnings and error messages from
the ALLBASE/SQL message catalog have been displayed.
* In the case of any other errors, the program displays all
available messages, then returns to subprogram unit SelectQuery
and prompts the user for another PartNumber.
The code routine located at Label 3000 is executed when only a warning
condition results during execution of the SELECT command. This code
routine displays a message and the row of data retrieved, commits work,
and then prompts the user for another PartNumber.
The NOT FOUND condition that may be associated with the SELECT command is
handled by the code routine located at Label 4000. This code routine
displays the message, Row not found!, then passes control to subprogram
unit EndTransaction. SQLEXPLAIN does not provide a message for the NOT
FOUND condition, so the program must provide one itself.
_______________________________________________________________________________
| |
| PROGRAM forex5 |
| C |
| C ****************************************************** |
| C * This program illustrates the use of SQL's SELECT * |
| C * command to retrieve one row or tuple of data at * |
| C * a time. BEGIN WORK is executed before the SELECT * |
| C * and COMMIT WORK is executed after the SELECT. An * |
| C * indicator variable is used for SalesPrice. * |
| C * This program is like forex2 except this program * |
| C * handles deadlocks and error handling differently. * |
| C ****************************************************** |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C |
| C **************************************************** |
| C * Data Type Conversions : * |
| C * Character = SQL Char(1) * |
| C * Character*n = SQL Char(n) * |
| C * Character*n = SQL VarChar * |
| C * Double Precision = SQL Float * |
| C * Double Precision = SQL Decimal * |
| C * Integer = SQL Integer * |
| C * Integer*2 = SQL SmallInt * |
| C **************************************************** |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| EXEC SQL END DECLARE SECTION |
| C |
| C (* End Host Variable Declarations *) |
| C |
| C (* Beginning of the Main Program *) |
| C |
| WRITE (*,*) CHAR(27), 'U' |
| WRITE (*,*) 'Program to SELECT specified rows from the Parts table|
| 1 -- forex5' |
| WRITE (*,*) 'Event List:' |
| WRITE (*,*) ' CONNECT TO PartsDBE' |
| WRITE (*,*) ' BEGIN WORK' |
| WRITE (*,*) ' SELECT a specified row from the Parts table until u|
| 1ser enters a "/"' |
| WRITE (*,*) ' COMMIT WORK' |
| WRITE (*,*) ' RELEASE PartsDBE' |
| |
_______________________________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking
___________________________________________________________
| |
| C |
| CALL ConnectDBE |
| CALL SelectQuery |
| CALL TerminateProgram |
| C |
| STOP |
| END |
| C |
| C (* Beginning of the Sub-Routines *) |
| C |
| SUBROUTINE ConnectDBE |
| C (* Subroutine to Connect to PartsDBE *)|
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| EXEC SQL END DECLARE SECTION |
| C |
| EXEC SQL WHENEVER SQLERROR GOTO 1000 |
| C |
| WRITE (*,*) ' ' |
| WRITE (*,*) 'CONNECT TO PartsDBE' |
| EXEC SQL CONNECT TO 'PartsDBE' |
| GOTO 1100 |
| C |
| 1000 CALL SQLStatusCheck |
| CALL TerminateProgram |
| C |
| 1100 RETURN |
| EXEC SQL WHENEVER SQLERROR CONTINUE |
| END |
| C (* End of ConnectDBE Subroutine *) |
| C |
| C |
| SUBROUTINE BeginTransaction |
| C (* Subroutine to Begin Work *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| |
| |
| |
___________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 2 of 8)
__________________________________________________________
| |
| C (* Begin Host Variable Declarations *)|
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| EXEC SQL END DECLARE SECTION |
| C |
| EXEC SQL WHENEVER SQLERROR GOTO 1000 |
| C |
| WRITE (*,*) 'BEGIN WORK' |
| EXEC SQL BEGIN WORK |
| GOTO 1100 |
| C |
| 1000 CALL SQLStatusCheck |
| CALL TerminateProgram |
| C |
| 1100 RETURN |
| EXEC SQL WHENEVER SQLERROR CONTINUE |
| END |
| C (* End BeginTransaction Subroutine *) |
| C |
| C |
| SUBROUTINE EndTransaction |
| C (* Subroutine to Commit Work *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| C (* Begin Host Variable Declarations *)|
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| EXEC SQL END DECLARE SECTION |
| C |
| EXEC SQL WHENEVER SQLERROR GOTO 1000 |
| C |
| WRITE (*,*) 'COMMIT WORK' |
| EXEC SQL COMMIT WORK |
| GOTO 1100 |
| C |
| 1000 CALL SQLStatusCheck |
| CALL TerminateProgram |
| C |
| 1100 RETURN |
| EXEC SQL WHENEVER SQLERROR CONTINUE |
| END |
| C (* End EndTransaction Subroutine *) |
| |
| |
| |
__________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 3 of 8)
____________________________________________________________
| |
| C |
| C |
| SUBROUTINE TerminateProgram |
| C (* Subroutine to Release PartsDBE *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| EXEC SQL END DECLARE SECTION |
| C |
| WRITE (*,*) 'RELEASE PartsDBE' |
| EXEC SQL RELEASE |
| WRITE (*,*) 'Terminating Program' |
| RETURN |
| END |
| C (* End ReleaseDBE Subroutine *) |
| C |
| C |
| SUBROUTINE SelectQuery |
| C (* Subroutine to prompt user for Query Input *)|
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| LOGICAL SQLCommandDone |
| CHARACTER*16 response |
| INTEGER trycounter |
| INTEGER multiplerows |
| INTEGER deadlock |
| INTEGER OK |
| INTEGER notfound |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| CHARACTER*16 PartNumber |
| CHARACTER*30 PartName |
| DOUBLE PRECISION SalesPrice |
| SQLIND SalesPriceInd |
| EXEC SQL END DECLARE SECTION |
| |
| |
| |
____________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 4 of 8)
_______________________________________________________________________________
| |
| C |
| EXEC SQL WHENEVER SQLERROR GOTO 2000 |
| EXEC SQL WHENEVER SQLWARNING GOTO 3000 |
| EXEC SQL WHENEVER NOT FOUND GOTO 4000 |
| C |
| trycounter = 0 |
| multiplerows = -10002 |
| 1000 CONTINUE |
| DO WHILE (PartNumber .NE. '/') |
| SQLCommandDone = .TRUE. |
| WRITE (*,100) |
| 100 FORMAT(/$,' Enter PartNumber from Parts table or / to STOP > ')|
| READ (5,110) PartNumber |
| 110 FORMAT(A16) |
| IF (PartNumber .NE. '/') THEN |
| CALL BeginTransaction |
| C |
| DO WHILE (SQLCommandDone) |
| C |
| WRITE (*,*) 'SELECT PartNumber, PartName, SalesPrice' |
| C |
| EXEC SQL SELECT PartNumber, PartName, SalesPrice |
| 1 INTO :PartNumber, |
| 2 :PartName, |
| 3 :SalesPrice :SalesPriceInd |
| 4 FROM PurchDB.Parts |
| 5 WHERE PartNumber = :PartNumber |
| C |
| SQLCommandDone = .FALSE. |
| CALL DisplayRow (PartNumber,PartName,SalesPrice, |
| 1 SalesPriceInd) |
| END DO |
| CALL EndTransaction |
| ENDIF |
| END DO |
| GOTO 5000 |
| C |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
_______________________________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 5 of 8)
___________________________________________________________________________
| |
| 2000 IF (SQLCode .EQ. multiplerows) THEN |
| WRITE (*,*) 'WARNING: More than one row qualifies!' |
| ENDIF |
| CALL SQLStatusCheck (trycounter) |
| CALL DisplayRow (PartNumber,PartName,SalesPrice,SalesPriceInd)|
| CALL EndTransaction |
| GOTO 1000 |
| C |
| 3000 WRITE (*,*) 'An SQL WARNING has occurred. The following row' |
| WRITE (*,*) 'of data may not be valid! ' |
| CALL DisplayRow (PartNumber,PartName,SalesPrice,SalesPriceInd)|
| CALL EndTransaction |
| GOTO 1000 |
| C |
| 4000 WRITE (*,*) 'Row not found!' |
| CALL EndTransaction |
| GOTO 1000 |
| C |
| 5000 RETURN |
| EXEC SQL WHENEVER SQLERROR CONTINUE |
| EXEC SQL WHENEVER SQLWARNING CONTINUE |
| EXEC SQL WHENEVER NOT FOUND CONTINUE |
| END |
| C |
| C (* End QueryTable Subroutine *) |
| C |
| C |
| SUBROUTINE SQLExplain |
| C (* Subroutine to CALL SQLExplain *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| CHARACTER*80 SQLMessage |
| EXEC SQL END DECLARE SECTION |
| C |
| EXEC SQL SQLEXPLAIN :SQLMessage |
| WRITE (*,*) SQLMessage |
| C |
| RETURN |
| END |
| C |
| C (* End SQLExplain Subroutine *) |
| |
___________________________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 6 of 8)
_____________________________________________________________________________
| |
| SUBROUTINE SQLStatusCheck (trycounter) |
| C (* Subroutine to Check for DeadLocks *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| LOGICAL SQLCommandDone |
| LOGICAL Abort |
| INTEGER deadlock |
| INTEGER trycounter |
| INTEGER trycounterlimit |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| CHARACTER*80 SQLMessage |
| EXEC SQL END DECLARE SECTION |
| C |
| deadlock = -14024 |
| trycounterlimit = 3 |
| SQLCommandDone = .FALSE. |
| C |
| IF (SQLCode .EQ. deadlock) THEN |
| IF (trycounter .EQ. trycounterlimit) THEN |
| SQLCommandDone = .TRUE. |
| WRITE (*,*) 'Deadlock occurred. You may want to try again'|
| ELSE |
| trycounter = trycounter + 1 |
| SQLCommandDone = .FALSE. |
| ENDIF |
| ENDIF |
| Abort = .FALSE. |
| IF (SQLCode .LT. deadlock) THEN |
| Abort = .TRUE. |
| ENDIF |
| DO WHILE (SQLCode .NE. 0) |
| CALL SQLExplain |
| END DO |
| C |
| IF (Abort) THEN |
| CALL TerminateProgram |
| ENDIF |
| C |
| RETURN |
| END |
| C |
| C (* End DeadLockCheck Subroutine *) |
_____________________________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 7 of 8)
_____________________________________________________________________
| |
| C |
| C |
| SUBROUTINE DisplayRow (PartNumber,PartName,SalesPrice, |
| 1SalesPriceInd) |
| C (* Subroutine to Display a Selected Row *) |
| C |
| EXEC SQL INCLUDE SQLCA |
| C |
| C (* Begin SQL Communication Area *) |
| C |
| C (* Begin Host Variable Declarations *) |
| C |
| EXEC SQL BEGIN DECLARE SECTION |
| CHARACTER*16 PartNumber |
| CHARACTER*30 PartName |
| DOUBLE PRECISION SalesPrice |
| SQLIND SalesPriceInd |
| CHARACTER*80 SQLMessage |
| EXEC SQL END DECLARE SECTION |
| C |
| WRITE(*,100) PartNumber |
| WRITE(*,110) PartName |
| C |
| C IF (SalesPriceInd .LT. 0) THEN |
| IF (SalesPrice .LT. 0) THEN |
| WRITE (*,*) 'Sales Price is NULL' |
| ELSE |
| WRITE(*,120) SalesPrice |
| ENDIF |
| ENDIF |
| 100 FORMAT(' Part Number: ',A16) |
| 110 FORMAT(' Part Name: ',A30) |
| 120 FORMAT(' Sales Price: ',F10.2) |
| C |
| WRITE (*,*) 'Was retrieved from the PurchDB.Parts table'|
| C |
| RETURN |
| END |
| C (* End DisplayRow Subroutine *) |
| |
| |
| |
| |
| |
| |
| |
| |
| |
_____________________________________________________________________
Figure 5-1. Program forex5: Implicit and Explicit Status Checking (page 8 of 8)
Explicit Status Checking
The example examined under "Implicit Status Checking" has already
illustrated several uses for explicit status checking:
PROGRAM SQLError
:
C (* Restart/Reentry point *)
600 CONTINUE
.
. SQL SELECT Command
.
IF (SQLCode .EQ. MultipleRows) THEN
WRITE(6,602) 'WARNING: More than one row qualifies.'
602 FORMAT(A80)
ELSE
CALL SQLStatusCheck (trycounter)
ENDIF
CALL DisplayRow (PartNumber,PartName,SalesPrice,SalesPriceInd)
CALL EndTransaction
GOTO 600
:
END
C
SUBROUTINE SQLStatusCheck (trycounter)
:
IF (SQLCode .EQ. deadlock) THEN
IF (TryCounter .EQ. TryCounterLimit) THEN
WRITE(6,102) 'Deadlock occurred, you may want to try again.'
102 FORMAT(A80)
CALL TerminateProgram
ELSE
trycounter = trycounter + 1
ENDIF
ENDIF
Abort = .FALSE.
IF (SQLCode .LT. deadlock) THEN
Abort = .TRUE.
ENDIF
DO WHILE (SQLCode .NE. 0)
CALL SQLExplain :SQLMessage
CALL WriteOut (SQLMessage)
END DO
IF (Abort) THEN
CALL TerminateProgram
ENDIF
:
RETURN
END
SQLCA values are explicitly examined in this example in order to:
* Isolate errors so critical that they caused ALLBASE/SQL to
rollback the current transaction.
* Control the number of times SQLEXPLAIN is executed.
* Detect when more than one row qualifies for the SELECT operation.
* Detect when a deadlock condition exists and control program
execution.
This section examines when you may want to invoke such status-checking
code routines explicitly rather than implicitly. In addition, this
section illustrates how SQLErrd(3) and several SQLCode values can be
explicitly used to monitor the number of rows operated on by data
manipulation commands.
Explicitly Invoking Status-Checking Subprogram Units.
The example in Figure 5-1 illustrates how status-checking code can be
consolidated within individual subprogram units. This approach can
sometimes reduce the amount of status-checking code. As the number of
SQL operations in a program increases, however, the likelihood of needing
to return to different places in the program after execution of such a
subprogram unit increases. In this case, you invoke the subprogram units
after explicitly checking SQLCA values rather than using the WHENEVER
command to implicitly check these values.
The example shown in Figure 5-2 contains four data manipulation
operations: INSERT, UPDATE, DELETE, and SELECT. Each of these operations
is executed from its own subprogram unit.
As in the program in Figure 5-1, one subprogram unit is used for explicit
error handling: SQLStatusCheck. Unlike the program in Figure 5-2;
however, this subprogram unit is invoked after explicit test of SQLCode
is made, immediately following each data manipulation operation. In the
program in Figure 5-2, tests for warning conditions are omitted.
Because error handling is performed in a subprogram unit rather than in a
code routine following the embedded SQL command, control returns to the
point in the program where SQLStatusCheck is invoked.
________________________________________________________________________
| |
| PROGRAM Main |
| . |
| . |
| . |
| CALL SelectActivity |
| . |
| . |
| . |
| STOP |
| END |
| |
| SUBROUTINE SelectActivity |
| |
| This subprogram unit prompts for a number that indicates|
| whether the user wants to SELECT, UPDATE, DELETE, |
| or INSERT rows, then invokes the subprogram unit that |
| accomplishes the selected activity. The DONE flag |
| is set when the user enters a slash. |
| . |
| . |
| . |
| RETURN |
| END |
| |
| SUBROUTINE InsertData |
| . |
| . |
| . |
| Statements that accept data from the user appear here. |
| |
| EXEC SQL INSERT |
| 1 INTO PurchDB.Parts (PartNumber, |
| 2 PartName, |
| 3 SalesPrice) |
| 4 VALUES (:PartNumber, |
| 5 :PartName, |
| 6 :SalesPrice) |
| |
| IF (SQLCode .NE. OK) THEN |
| CALL SQLStatusCheck 3 |
| |
| ENDIF |
| . |
| . |
| . |
| RETURN |
| END |
| SUBROUTINE UpdateData |
________________________________________________________________________
Figure 5-2. Explicitly Invoking Status-Checking Subprogram Units
_________________________________________________________________________________
| |
| . |
| . |
| . |
| This subprogram unit verifies that the row(s) to be changed |
| exist, then invokes subprogram unit DisplayUpdate to accept |
| new data from the user. |
| |
| EXEC SQL SELECT PartNumber, PartName, SalesPrice |
| 1 INTO :PartNumber, |
| 2 :PartName, |
| 3 :SalesPrice |
| 4 FROM PurchDB.Parts |
| 5 WHERE PartNumber = :PartNumber |
| |
| IF (SQLCode .EQ. OK) THEN |
| CALL DisplayUpdate |
| ELSE |
| IF (SQLCode .EQ. MultipleRows) THEN |
| WRITE(6,102) 'Warning; more than one row qualifies!' |
| 102 FORMAT (A80) |
| CALL DisplayUpdate |
| ELSE |
| IF (SQLCode .EQ. NotFound) THEN 5 |
| |
| WRITE (6,103) 'Row not found!' |
| 103 FORMAT (A80) |
| ELSE |
| CALL SQLStatusCheck 3 |
| |
| ENDIF |
| ENDIF |
| ENDIF |
| . |
| |
| SUBROUTINE DisplayUpdate |
| . |
| . |
| . |
| Statements that prompt user for new data appear here. |
| EXEC SQL UPDATE PurchDB.Parts |
| 1 SET PartName = :PartName, |
| 2 SalesPrice = :SalesPrice, |
| 3 WHERE PartNumber = :PartNumber |
| |
| IF (SQLCode .NE. OK) THEN 3 |
| |
| CALL SQLStatusCheck |
| ENDIF |
| . |
_________________________________________________________________________________
Figure 5-2. Explicitly Invoking Status-Checking Subprogram Units (page 2 of 5)
_________________________________________________________________________________
| |
| . |
| . |
| RETURN |
| END |
| |
| SUBROUTINE DeleteData |
| . |
| . |
| . |
| This subprogram unit verifies that the row(s) to be deleted |
| exist, then invokes subprogram unit DisplayDelete to delete |
| the row(s). |
| |
| EXEC SQL SELECT PartNumber, PartName, SalesPrice |
| 1 INTO :PartNumber, |
| 2 :PartName, |
| 3 :SalesPrice |
| 4 FROM PurchDB.Parts |
| 5 WHERE PartNumber = :PartNumber |
| |
| IF (SQLCode .EQ. OK) THEN |
| CALL DisplayDelete |
| ELSE |
| IF (SQLCode .EQ. MultipleRows) THEN |
| WRITE(6,102) 'Warning; more than one row qualifies!' |
| 102 FORMAT(A80) |
| CALL DisplayDelete |
| ELSE |
| IF (SQLCode = NotFound) THEN 5 |
| |
| WRITE (6,103) 'Row not found!' |
| 103 FORMAT(A80) |
| ELSE |
| CALL SQLStatusCheck 3 |
| |
| ENDIF |
| ENDIF |
| ENDIF |
| . |
| . |
| . |
| RETURN |
| END |
| |
| SUBROUTINE DisplayDelete |
| . |
| . |
| . |
| |
_________________________________________________________________________________
Figure 5-2. Explicitly Invoking Status-Checking Subprogram Units (page 3 of 5)
_________________________________________________________________________________
| |
| Statements that verify that the deletion should |
| actually occur appear here. |
| |
| EXEC SQL DELETE FROM PurchDB.Parts |
| 1 WHERE PartNumber = :PartNumber |
| |
| IF (SQLCode .NE. OK) THEN 3 |
| |
| CALL SQLStatusCheck |
| ENDIF |
| . |
| . |
| . |
| RETURN |
| END |
| |
| SUBROUTINE SelectData |
| . |
| . |
| . |
| Statements that prompt for a partnumber appear here. |
| |
| EXEC SQL SELECT PartNumber, PartName, SalesPrice |
| 1 INTO :PartNumber, |
| 2 :PartName, |
| 3 :SalesPrice |
| 4 FROM PurchDB.Parts |
| 5 WHERE PartNumber = :PartNumber |
| |
| IF (SQLCode .EQ. OK) THEN |
| CALL DisplayRow |
| ELSE |
| IF (SQLCode .EQ. MultipleRows) THEN |
| WRITE(6,102) 'Warning; more than one row qualifies!' |
| 102 FORMAT(A80) |
| ELSE |
| IF (SQLCode = NotFound) THEN 5 |
| |
| WRITE (6,103) 'Row not found!' |
| 103 FORMAT(A80) |
| ELSE |
| CALL SQLStatusCheck 3 |
| |
| ENDIF |
| ENDIF |
| ENDIF |
| . |
| . |
| RETURN |
| END |
_________________________________________________________________________________
Figure 5-2. Explicitly Invoking Status-Checking Subprogram Units (page 4 of 5)
________________________________________________________________________________
| |
| SUBROUTINE SQLStatusCheck |
| . |
| . |
| . |
| IF (SQLCode .EQ. DeadLock) THEN |
| IF (trycounter .EQ. trycounterlimit) THEN |
| WRITE(6,102) 'Deadlock occurred; you may want to try again.'|
| 102 FORMAT(A80) |
| CALL EndTransaction |
| ELSE |
| trycounter = trycounter + 1 |
| ENDIF |
| ENDIF |
| Abort = .FALSE. |
| IF (SQLCode .LT. DeadLock) THEN |
| Abort = .TRUE. |
| ENDIF |
| DO WHILE (SQLCode .NE. 0) |
| EXEC SQL SQLEXPLAIN :SQLMessage |
| CALL WriteOut (SQLMessage) |
| END DO |
| IF (Abort) THEN |
| CALL TerminateProgram |
| ENDIF |
| . |
| . |
| . |
| RETURN |
| END |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
________________________________________________________________________________
Figure 5-2. Explicitly Invoking Status-Checking Subprogram Units (page 5 of 5)
Explicitly Checking for Number of Rows.
SQLErrd(3) is useful in determining how many rows were processed in one
of the following operations when the operation could be executed without
error:
SELECT
INSERT
UPDATE
DELETE
FETCH
UPDATE WHERE CURRENT
DELETE WHERE CURRENT
The SQLErrd(3) value can be used in these cases only when SQLCode does
not contain a negative number. When SQLCode is 0, SQLErrd(3) is always
equal to 1 for SELECT, FETCH, UPDATE WHERE CURRENT, and DELETE WHERE
CURRENT operations. SQLErrd(3) may be greater than 1 if more than one
row qualifies for an INSERT, UPDATE, or DELETE operation. When SQLCode
is 100, SQLCA.SQLErrd(3) is 0.
The remainder of this chapter examines techniques for explicitly checking
SQLErrd(3) as well as using SQLCodes of 100 and -10002 in data
manipulation logic.
Using SQLErrd(3) for UPDATE and DELETE Operations.
The example in Figure 5-3 could be modified to display the number of rows
updated or deleted by using SQLErrd(3). In the case of the update
operation, for example, the actual number of rows updated could be
displayed after the UPDATE command is executed:
SUBROUTINE DisplayUpdate
.
.
EXEC SQL INCLUDE SQLCA
C
INTEGER OK
INTEGER NumberOfRows
C
EXEC SQL BEGIN DECLARE SECTION
CHARACTER*16 PartNumber
CHARACTER*30 PartName
DOUBLE PRECISION SalesPrice
EXEC SQL END DECLARE SECTION
.
.
Statements that prompt user for new data appear here.
EXEC SQL UPDATE PurchDB.Parts
1 SET PartName = :PartName,
2 SalesPrice = :SalesPrice,
3 WHERE PartNumber = :PartNumber
IF (SQLCode .EQ. OK) THEN
NumberOfRows = SQLErrd(3)
WRITE(6,102) 'The number of rows updated was: ', NumberOfRows
102 FORMAT(A80,I)
ELSE
WRITE(6,103) 'No rows could be updated!'
103 FORMAT(A80)
CALL SQLStatusCheck
ENDIF
.
.
RETURN
END
If the UPDATE command is successfully executed, SQLCode equals zero and
SQLErrd(3) contains the number of rows updated. If the UPDATE command
cannot be successfully executed, SQLCode contains a negative number and
SQLErrd(3) contains a zero.
In the case of the delete operation, the actual number of rows deleted
could be displayed after the DELETE command is executed:
SUBROUTINE DisplayDelete
.
.
EXEC SQL INCLUDE SQLCA
C
INTEGER OK
INTEGER NumberOfRows
CHARACTER response
C
EXEC SQL BEGIN DECLARE SECTION
CHARACTER*16 PartNumber
CHARACTER*30 PartName
DOUBLE PRECISION SalesPrice
EXEC SQL END DECLARE SECTION
.
.
Statements that verify that the deletion should
actually occur appear here.
EXEC SQL DELETE FROM PurchDB.Parts
1 WHERE PartNumber = :PartNumber
IF (SQLCode .EQ. OK) THEN
NumberOfRows = SQLErrd(3)
WRITE(6,102) 'The number of rows deleted was: ', NumberOfRows
102 FORMAT(A35,I)
WRITE(6,103) 'Do you want to COMMIT WORK? Y or N:'
103 FORMAT(A80)
READ(5,104) response
104 FORMAT(A1)
IF (response .EQ. 'Y') THEN
EXEC SQL COMMIT WORK
ELSE
EXEC SQL ROLLBACK WORK
ENDIF
ELSE
CALL SQLStatusCheck
ENDIF
.
.
RETURN
END
If the DELETE command is successfully executed, SQLCode equals 0 and
SQLErrd(3) contains the number of rows deleted. If the DELETE command
cannot be successfully executed, SQLCode contains a negative number and
SQLErrd(3) contains a 0.
Using SQLCode of 100.
The programs already examined in this chapter have illustrated how an
SQLCode of 100 can be detected and handled for data manipulation commands
that do not use a cursor. When a cursor is being used, this SQLCode
value is used to determine when all rows in an active set have been
fetched:
SUBROUTINE Cursor
.
.
EXEC SQL INCLUDE SQLCA
C
INTEGER OK
INTEGER NotFound
LOGICAL donefetch
C
EXEC SQL BEGIN DECLARE SECTION
CHARACTER*16 PartNumber
CHARACTER*30 PartName
DOUBLE PRECISION SalesPrice
EXEC SQL END DECLARE SECTION
.
.
CALL DeclareCursor
C
EXEC SQL OPEN Cursor1
.
.
DO WHILE (donefetch)
CALL FetchRow (donefetch)
END DO
.
.
RETURN
END
SUBROUTINE FetchRow (donefetch)
.
.
EXEC SQL FETCH Cursor1
1 INTO :PartNumber,
2 :PartName,
3 :SalesPrice
IF (SQLCode .EQ. OK) THEN
CALL DisplayRow
ELSE
IF (SQLCode .EQ. NotFound) THEN
donefetch = .FALSE.
WRITE(6,102) ' '
WRITE(6,102) 'Row not found or no more rows!'
102 FORMAT(A80)
ELSE
CALL DisplayError
ENDIF
ENDIF
.
.
RETURN
END
In this example, the active set is defined when the OPEN command is
executed. The cursor is then positioned before the first row of the
active set. When the FETCH command is executed, the first row in the
active set is placed into the program's host variables, then displayed.
The FETCH command retrieves one row at a time into the host variables
until the last row in the active set has been retrieved; after the last
row has been fetched from the active set the next attempt to FETCH sets
SQLCode to a value of 100. If no rows qualify for the active set,
SQLCode equals 100 the first time subprogram unit FetchRow is executed.
Using SQLCode of -10002.
If more than one row qualifies for a SELECT or FETCH operation,
ALLBASE/SQL sets SQLCode to -10002. The program in Figure 5-3 contains
an explicit test for this value. When SQLCode is equal to MultipleRows
(defined as -10002 in the Type Declaration Section), a status checking
subprogram unit is not invoked, but a warning message is displayed:
SUBROUTINE UpdateData
.
.
EXEC SQL INCLUDE SQLCA
C
INTEGER OK
INTEGER NotFound
INTEGER MultipleRows
LOGICAL donefetch
C
EXEC SQL BEGIN DECLARE SECTION
CHARACTER*16 PartNumber
CHARACTER*30 PartName
DOUBLE PRECISION SalesPrice
EXEC SQL END DECLARE SECTION
C
OK = 0
NotFound = 100
MultipleRows = -10002
.
.
This subprogram unit verifies that the row(s) to be changed
exists, then invokes subprogram unit DisplayUpdate to accept
new data from the user.
.
.
EXEC SQL SELECT PartNumber, PartName, SalesPrice
1 INTO :PartNumber,
2 :PartName,
3 :SalesPrice
4 FROM PurchDB.Parts
5 WHERE PartNumber = :PartNumber
IF (SQLCode .EQ. OK) THEN
CALL DisplayUpdate
ELSE
IF (SQLCode .EQ. MultipleRows) THEN
WRITE(6,102) ' '
WRITE(6,102) 'Warning; more than one row will be changed!'
102 FORMAT(A80)
CALL DisplayUpdate
ELSE
IF (SQLCode .EQ. NotFound) THEN
WRITE(6,103) ' '
WRITE(6,103) 'Row not found.')
103 FORMAT(A80)
ELSE
CALL SQLStatusCheck
ENDIF
ENDIF
ENDIF
.
.
RETURN
END