[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

Compaq ACMS for OpenVMS
Writing Server Procedures


Previous Contents Index

4.1.2.1 Defining an SQL Context Structure

In your procedure, you must define a context structure that holds the TID associated with the distributed transaction.

The following code segment illustrates how to define an SQL context structure using COBOL:


    WORKING-STORAGE SECTION.
               .
               .
               .
    01 context-structure.
            02 cs-version           PIC S9(9) COMP VALUE 1.
            02 cs-type              PIC S9(9) COMP VALUE 1.
            02 cs-length            PIC S9(9) COMP VALUE 16.
            02 cs-tid               PIC X(16).
            02 cs-end               PIC S9(9) COMP VALUE 0.
               .
               .
               .

Alternatively, you can use a library to hold the context structure and refer to this library in your procedure. For example:


    WORKING-STORAGE SECTION.
               .
               .
               .
    EXEC SQL
        INCLUDE 'AVERTZ_SOURCE:VR_CONTEXT_STRUCTURE_INCLUDE.LIB'
    END-EXEC.
               .
               .
               .

Appendix B contains the contents of the libraries referred to in examples from the AVERTZ sample application in this manual.

The following code segment illustrates how to define an SQL context structure using BASIC:


    RECORD sql_context_structure
        LONG sqlctx_version
        LONG sqlctx_type
        LONG sqlctx_length
        STRING sqlctx_tid = 16
        LONG sqlctx_end
    END RECORD sqlctx_structure


    DECLARE sql_context_structure sqlcs

    sqlcs::sqlctx_version = 1%
    sqlcs::sqlctx_type = 1%
    sqlcs::sqlctx_length = 16%
    sqlcs::sqlctx_end = 0%

Alternatively, you can use a BASIC INCLUDE file to define and initialize the context structure and then include this file in your procedure. For example:


    %INCLUDE "pers_files:pers_sqlctx"

4.1.2.2 Storing the TID in the SQL Context Structure

You must call the ACMS$GET_TID service to obtain the TID and store it in the SQL context structure before you access the database.

The following code segment illustrates how to call the ACMS$GET_TID service to obtain the TID and store it in the SQL context structure using COBOL. If the ACMS$GET_TID service returns an error, the step procedure raises a nonrecoverable exception and exits.


    CALL "ACMS$GET_TID" USING BY REFERENCE cs-tid
                        GIVING ret-stat.
    IF ret-stat IS NOT SUCCESS
    THEN
        CALL "ACMS$RAISE_NONREC_EXCEPTION"
                        USING BY REFERENCE ret-stat
        GO TO 999-end
    END-IF.

The following code segment illustrates how to call the ACMS$GET_TID service to obtain the TID and store it in the SQL context structure using BASIC. If the ACMS$GET_TID service returns an error, the step procedure raises a nonrecoverable exception and exits.


    sts = ACMS$GET_TID( sqlcs::sqlctx_tid BY REF )
    IF ( sts AND 1% ) = 0% THEN
        CALL ACMS$RAISE_NONREC_EXCEPTION( sts )
        EXIT FUNCTION
    END IF

4.1.2.3 Passing the Context Structure to SQL

You must pass the context structure to SQL whenever you use SQL within a distributed transaction. This section describes how you pass the context structure to SQL when you are using precompiled SQL and SQL module language.

  • Using precompiled SQL
    When you use precompiled SQL, the context structure is passed using the CONTEXT parameter on the EXEC SQL phrase.
    The following code segment illustrates how to pass the context structure using precompiled SQL:


        EXEC SQL USING CONTEXT :context-structure
            SET TRANSACTION READ WRITE
            RESERVING reservations FOR SHARED WRITE,
                      rental_classes,sites,regions FOR SHARED READ
        END-EXEC.
    
  • Using SQL module language
    When you use SQL module language, you must pass the context structure as an argument on the call to the SQL procedure. When you compile the SQL module, you must use the /CONTEXT switch to generate an implicit context parameter for each procedure that participates in a distributed transaction. The context argument is always generated as the last argument in the argument list; therefore, always pass the context structure as the last argument when you call the SQL procedure.
    The following code segment illustrates the module header and the first procedure in an SQL module language program for use by a BASIC program:


       -- Header section
       MODULE          pers_appl_procs
       LANGUAGE        BASIC
       AUTHORIZATION   RDB$DBHANDLE
       -- Declare schema
       DECLARE PARTS SCHEMA FOR FILENAME 'pers_db:personnel'
       -- Start transaction procedure
       PROCEDURE start_new_employee_trans
           SQLCODE;
       --      Start the transaction
               SET TRANSACTION READ_WRITE
                   RESERVING employees FOR SHARED WRITE,
                             history FOR SHARED WRITE;
       -- Additional procedures
                .
                .
                .
    

    The following code segment illustrates how to call the START_NEW_EMPLOYEE_TRANS SQL procedure from a BASIC program. Note that the SQL context structure is passed as the last argument in the call to the SQL procedure.


                   .
                   .
                   .
       CALL start_new_employee_trans( sqlsts, sqlcs )
                   .
                   .
                   .
    

4.1.3 Starting and Ending SQL Database Transactions

You start an SQL database transaction by using a SET TRANSACTION statement. However, the way in which you start the database transaction depends on whether the database transaction is part of a distributed transaction.

This section describes how to start a database transaction that is part of a distributed transaction and how to start and end an independent database transaction. In addition, this section discusses various access modes that you can specify when starting a database transaction.

4.1.3.1 Starting an SQL Database Transaction that is Part of a Distributed Transaction

You must specify the SQL context structure when you start a database transaction that is part of a distributed transaction. For example:


    EXEC SQL USING CONTEXT :context-structure
        SET TRANSACTION READ WRITE
        RESERVING reservations FOR SHARED WRITE,
                  rental_classes,sites,regions FOR SHARED READ
    END-EXEC.

Note

You must specify the SQL context structure on every SQL verb that is executed within the distributed transaction. The step procedure does not function correctly if you omit the SQL context structure on an SQL statement.

Because the SQL database transaction is participating in a distributed transaction, Rdb automatically commits or rolls back the database transaction when the distributed transaction ends. Therefore, you must not use the COMMIT or ROLLBACK verbs to end the database transaction.

4.1.3.2 Starting and Ending an Independent SQL Database Transaction

You start an independent database transaction by using a SET TRANSACTION statement. For example:


    EXEC SQL USING CONTEXT
        SET TRANSACTION READ WRITE
        RESERVING reservations FOR SHARED WRITE,
                  rental_classes,sites,regions FOR SHARED READ
    END-EXEC.

Because the SQL database transaction is not participating in a distributed transaction, you must commit or roll back the database transaction in the procedure. For example:


    IF step-proc-status IS SUCCESS
    THEN
        EXEC SQL
            COMMIT
        END-EXEC
    ELSE
        EXEC SQL
            ROLLBACK
        END-EXEC
    END-IF.

4.1.3.3 Using Rdb Transaction Mode and Lock Mode Specifications

Specify the transaction mode and the lock mode when you start an Rdb database transaction.

The transaction mode specifies how the step procedure accesses the database. If the step procedure only reads records from the database, specify READ ONLY when you start the database transaction. Otherwise, specify READ WRITE in step procedures that read, write, and modify records in the database.

If you do not specify a mode, the SQL default for the SET TRANSACTION statement is READ WRITE, which means that you can both read records from specified tables and write data into them. If you are using RDO, the default is READ ONLY, which means that you can only read records from the database; you cannot update existing records or store new records in the database. Specifying READ ONLY in a procedure that does not write or modify records reduces contention in the database.

Note

When you use an Rdb database, any records you access are not locked until you modify them. Once a record has been modified, it remains locked until the end of the transaction.

The lock mode specifies how the step procedure accesses specific relations in the database. To reduce contention in the database, specify explicitly which relations you access in the database when you start an Rdb transaction. For each relation, specify read or write access to the relation depending on the access the server requires. For example, if the step procedure only reads records, specify READ access. If the server procedure reads, writes, and modifies records in the relation, specify WRITE access.

Refer to the Rdb documentation for an explanation of the Rdb share modes and the defaults for the keywords you use with the SET TRANSACTION statement in SQL and with the START_TRANSACTION statement in RDO and RDML.

Example 4-3 illustrates how the step procedure VR_COMPLETE_CHECKOUT_PROC starts the database transaction, specifying the transaction mode and the relations it accesses, along with the lock specifications.

Example 4-3 Lock Specification Example

     EXEC SQL USING CONTEXT :CONTEXT-STRUCTURE
             SET TRANSACTION READ WRITE
              .
              .
              .
             RESERVING  RESERVATIONS,
                        VEHICLES,
                        VEHICLE_RENTAL_HISTORY
             FOR        SHARED WRITE,
                        RENTAL_CLASSES,
                        SITES,
                        REGIONS
             FOR        SHARED READ
     END-EXEC.

The RESERVATIONS, VEHICLES, and VEHICLE_RENTAL_HISTORY relations are reserved for SHARED WRITE, which means that no other user can modify the records you are updating once they have been modified; other users can, however, read records that you are reading or modifying. Until you commit a modification, other users read the original version of the record.

Also shown in Example 4-3, the RENTAL_CLASSES, SITES, and REGIONS relations are reserved for SHARED READ; this means that other users can read and modify the same records that you are accessing in the relation.

ACMS tasks typically perform a transaction with SHARED access because the database is shared by more than one server process. You might occasionally need to lock an entire relation when you access it; if you need to do so, refer to the SQL documentation on PROTECTED and EXCLUSIVE access.

4.1.3.4 Using an Rdb Wait Mode Specification

The SQL SET TRANSACTION and RDO START_TRANSACTION statements also allow you to specify a wait mode. Using the wait mode, you specify how Rdb handles the situation if it encounters a locked relation or record while accessing the database. If you specify WAIT, the default, Rdb waits until the lock can be granted before continuing. If you specify NOWAIT, Rdb immediately returns an error if it encounters a lock.

If you choose to wait for locks, you can specify the maximum time you are prepared to wait until a lock is granted. If the lock is not granted in the specified time limit, Rdb returns the RDMS$_TIMEOUT error. Specify the time limit by defining the RDM$BIND_LOCK_TIMEOUT_INTERVAL logical name in a logical name table that is accessible to the server. Define the RDM$BIND_LOCK_TIMEOUT_INTERVAL logical name:

  • As a server logical name in the application definition
  • In an application-specific logical name table
  • In the system logical name table
  • In a group logical name table

For example, the following server logical name definition specifies that Rdb should wait no more than 10 seconds for a lock to be granted:


   LOGICAL NAME IS
        RDM$BIND_LOCK_TIMEOUT_INTERVAL = "10";

Important

If you are using distributed transactions, always specify a lock timeout interval to ensure that ACMS can successfully cancel a task that is waiting for a database lock. By specifying a lock timeout interval, you ensure that the task will be canceled as soon as the timeout interval expires. If you do not specify a lock timeout interval, the task cannot be canceled until the lock is granted.

4.1.4 Reading from a Database

The procedure VR_COMPLETE_CHECKOUT_PROC from the AVERTZ Sample Application illustrates the use of SQL statements in reading information from an Rdb database. As part of the processing associated with checking out a car, the procedure must find the current odometer reading for the selected vehicle. It does this by selecting the record with the highest odometer reading from the VEHICLE_RENTAL_HISTORY relation. Because the vehicle history record might contain a null value, the procedure uses an indicator parameter to determine whether or not an odometer reading has been retrieved.

Example 4-4 illustrates how the procedure VR_COMPLETE_CHECKOUT_PROC declares an indicator array (for a subsequent STORE operation) and an indicator parameter (for the SELECT operation). You need to include this when a read operation on the database might return a null value. Example 4-4 shows one way this can appear in a COBOL program.

For detailed information and information on step procedures written in other high-level languages, see the SQL documentation.

Example 4-4 Indicator Array for Null Values

*
* Indicator array for null values
*
01 VR_VRH_IND_ARRAY.
   05 VR_VRH_IND OCCURS 6 TIMES  PIC S9(4) COMP.
01 VR_VRH_IND1                   PIC S9(4) COMP.

The section of code in Example 4-5 selects the record with the highest odometer reading from the VEHICLE_RENTAL_HISTORY relation, specifying an indicator parameter (RH_VRH_IND1) that SQL sets when retrieving the data, and places the value in a workspace field.

Example 4-5 Selecting a Value from a Table

GET-ODOMETER-READING.
* Get the last return odometer reading for the vehicle being
* checked out from the database.  If not found, ignore it.
        .
        .
        .
        EXEC SQL USING CONTEXT :CONTEXT-STRUCTURE
           SELECT MAX(RETURN_ODOMETER_READING)INTO
                 :VR_VEHICLE_RENTAL_HISTORY_WKSP.CHECKOUT_ODOMETER_READING
                    INDICATOR :VR_VRH_IND1
              FROM VEHICLE_RENTAL_HISTORY
              WHERE VEHICLE_ID = :VR_VEHICLES_WKSP.VEHICLE_ID
        END-EXEC.

4.1.5 Writing to a Database

Example 4-6 illustrates the use of SQL statements in writing to a database. The procedure updates the car reservation record and the vehicle record in the database. The procedure also writes a new vehicle rental history record to the database. The values of the RETURN_ODOMETER_READING and ACTUAL_RETURN_DATE fields are not known at the time the new history record is stored; therefore, the procedure uses an indicator array to store null values in the database for those fields. (Example 4-7 contains the complete procedure.)

Example 4-6 Writing to a Database

                      .
                      .
                      .
        MOVE NEG-ONE TO VR_VRH_IND(5).
        MOVE NEG-ONE TO VR_VRH_IND(6).
                      .
                      .
                      .

UPDATE-RESERVATION.
*
* Update the reservation in the database
*
        EXEC SQL USING CONTEXT :CONTEXT-STRUCTURE
           UPDATE RESERVATIONS
              SET CREDIT_CARD_NO = :VR_RESERVATIONS_WKSP.CREDIT_CARD_NO,
                  CREDIT_CARD_TYPE_ID =
                     :VR_RESERVATIONS_WKSP.CREDIT_CARD_TYPE_ID,
                  RESERV_STATUS_FLAG = :C-ONE,
                  RESERV_MODIFIC_FLAG =
                     :VR_RESERVATIONS_WKSP.RESERV_MODIFIC_FLAG,
                  BILL_RENTAL_CLASS_ID =
                     :VR_RESERVATIONS_WKSP.BILL_RENTAL_CLASS_ID,
                  VEHICLE_EXPECTED_RETURN_DATE =
                     :VR_RESERVATIONS_WKSP.VEHICLE_EXPECTED_RETURN_DATE
              WHERE RESERVATION_ID = :VR_RESERVATIONS_WKSP.RESERVATION_ID
        END-EXEC.


*
* Update the vehicle record in the database
*
UPDATE-VEHICLES.
        EXEC SQL USING CONTEXT :CONTEXT-STRUCTURE
           UPDATE VEHICLES
              SET CURRENT_SITE_ID =
                     :VR_RESERVATIONS_WKSP.VEHICLE_CHECKOUT_SITE_ID,
                  AVAILABLE_FLAG = :C-ZERO
              WHERE VEHICLE_ID = :VR_VEHICLES_WKSP.VEHICLE_ID
        END-EXEC.


*
* Write a new vehicle_rental_history record to the database
*
        EXEC SQL USING CONTEXT :CONTEXT-STRUCTURE
           INSERT INTO VEHICLE_RENTAL_HISTORY
              VALUES (:VR_VEHICLE_RENTAL_HISTORY_WKSP:VR_VRH_IND)
        END-EXEC.

4.1.6 Handling Errors

You typically write an error handler to process errors returned by Rdb when starting and ending a database transaction and when accessing data in the database. When you use Rdb with SQL, you have normal direct access to the same status values as you do when you use Rdb with RDO. The Rdb return status values are inherently compatible with OpenVMS usage.

Some Rdb errors are expected and are handled by resuming normal program execution. For example, Rdb returns an end-of-stream error when the last record in a record stream has been processed. In this case, the program can resume execution and process the records that have been read. Rdb can also return a number of recoverable errors that the program should check for and handle. For example, if Rdb returns a deadlock error, you might want to roll back the transaction and process the transaction again. Finally, Rdb can return a number of nonrecoverable errors. For example, a disk on which one of the database storage areas resides might fail. In this case, the program cannot continue until the problem has been resolved.

A distributed transaction can abort at any time. If a transaction aborts while a step procedure is executing, Rdb automatically rolls back an active database transaction. However, the step procedure will receive an error the next time it executes an SQL statement in a database transaction that was participating in the distributed transaction. Therefore, an error handler for a step procedure should check for and handle the errors that Rdb returns in this situation.

Typically, you want to retry a transaction automatically in the event of a recoverable error condition such as a deadlock, lock-conflict, lock-timeout, or transaction-timeout error. Rdb returns deadlock, lock-conflict, and lock-timeout errors to your step procedure when you access the database. In contrast, if a distributed transaction times out, the distributed transaction is aborted and ACMS raises a transaction exception in the task. In this case, Rdb returns an error if the step procedure accesses the database after the transaction has aborted.

There is an easy technique, illustrated in examples in this section, that allows you to simplify an exception handler that handles recoverable transaction exceptions in a task definition. The following list indicates how the error handler in the step procedure handles each type of error returned by Rdb:

  • Handling recoverable errors
    If an error handler in a step procedure detects a recoverable error condition, such as a deadlock, lock-conflict or lock-timeout error, it calls the ACMS$RAISE_TRANS_EXCEPTION service to raise a transaction exception using the ACMS$_TRANSTIMEDOUT exception code. If a distributed transaction does not complete within the specified time limit, ACMS also raises a transaction exception using the ACMS$_TRANSTIMEDOUT exception code. Therefore, using ACMS$_TRANSTIMEDOUT as the exception code in the step procedure means that the exception handler in the task definition has to test for only a single exception code in order to handle all recoverable transaction exceptions.
    If you detect a recoverable error in a step procedure using an independent database transaction that is not participating in a distributed transaction, you can roll back the database transaction and repeat the transaction in the step procedure.
  • Handling transaction aborts
    If a distributed transaction aborts while a step procedure is executing, Rdb returns one of a number of error status values. If a step procedure detects one of these errors, it raises a transaction exception using the error status. If the error was due to a distributed transaction aborting, ACMS overrides the exception in the task. However, if Rdb returns the error due to some other problem, the task is canceled with the specified exception code.
  • Handling nonrecoverable errors
    If an unexpected error occurs, the procedure uses the LIB$CALLG RTL routine to call LIB$SIGNAL to signal the error information returned by Rdb. If the procedure signals a fatal OpenVMS status, ACMS writes the error to the audit trail log, cancels the task, and runs down the server process. However, if the procedure signals an error or a warning OpenVMS status, ACMS continues executing the step procedure after writing the error to the audit trail log. The error handler also calls the ACMS$RAISE_NONREC_EXCEPTION service to ensure that the task is canceled.

The procedure VR_COMPLETE_CHECKOUT_PROC handles errors in the following manner:

  1. In the Working-Storage Section, the procedure obtains the structure for SQLCODE and RDB$MESSAGE_VECTOR:


        EXEC SQL INCLUDE SQLCA END-EXEC.
    
  2. In the Procedure Division, the step procedure instructs SQL to execute the instructions in the SQL_ERROR_HANDLER paragraph if an error occurs:


        EXEC SQL
            WHENEVER SQLERROR GO TO SQL-ERROR-HANDLER
        END-EXEC.
    
  3. In the SQL_ERROR_HANDLER paragraph, the procedure checks the error condition. If a recoverable error occurred, the procedure raises a transaction exception using ACMS$_TRANSTIMEDOUT as the exception code. If the distributed transaction aborted, the procedure raises a transaction exception using the error status returned by Rdb. If any other error occurred, the procedure signals the error information in the Rdb$MESSAGE_VECTOR structure and raises a nonrecoverable exception.


    SQL-ERROR-HANDLER.
    
         EVALUATE TRUE
             WHEN ( ( Rdb$LU_STATUS = RDB$_DEADLOCK ) OR
                    ( Rdb$LU_STATUS = RDMS$_DEADLOCK ) OR
                    ( Rdb$LU_STATUS = RDB$_LOCK_CONFLICT ) OR
                    ( Rdb$LU_STATUS = RDMS$_LCKCNFLCT ) OR
                    ( Rdb$LU_STATUS = RDMS$_TIMEOUT ) )
                 CALL "ACMS$RAISE_TRANS_EXCEPTION" USING                          BY REFERENCE ACMS$_TRANSTIMEDOUT
    
             WHEN ( ( RdB$LU_STATUS = RDB$_SYS_REQUEST_CALL ) OR
                    ( Rdb$LU_STATUS = RDB$_BAD_TRANS_HANDLE ) OR
                    ( Rdb$LU_STATUS = RDB$_DISTABORT ) OR
                    ( Rdb$LU_STATUS = RDB$_REQ_SYNC ) OR
                    ( Rdb$LU_STATUS = RDB$_READ_ONLY_TRANS ) )
                 CALL "ACMS$RAISE_TRANS_EXCEPTION" USING                          BY REFERENCE Rdb$LU_STATUS
    
             WHEN OTHER
                 CALL "LIB$CALLG" USING
                             BY REFERENCE Rdb$MESSAGE_VECTOR,
                             BY VALUE LIB$SIGNAL
                 CALL "ACMS$RAISE_NONREC_EXCEPTION" USING
                             BY REFERENCE Rdb$LU_STATUS
         END-EVALUATE.
    
  4. The task definition uses an exception handler action that repeats the transaction step up to five times if a recoverable transaction error occurs:


                 .
                 .
                 .
        EXCEPTION HANDLER
            SELECT FIRST TRUE OF
                ( ACMS$L_STATUS = vr_update_error ):
                    MOVE "TRAGN" TO vr_sendctrl_wksp.sendctrl_key;
                    GOTO STEP fix_cust_info;
                ( ACMS$L_STATUS = ACMS$_TRANSTIMEDOUT AND
                  vr_control_wksp.retry_count < 5 ):
                    REPEAT STEP;
    
                NOMATCH:
                    GET MESSAGE INTO vr_control_wksp.messagepanel;
                    MOVE "ACTWT" TO  vr_sendctrl_wksp.sendctrl_key,
                         "     " TO vr_control_wksp.ctrl_key;
                    GOTO STEP disp_stat;
            END SELECT;
                 .
                 .
                 .
    


Previous Next Contents Index