Examples of invoking CAF

The call attachment facility (CAF) enables programs to communicate with Db2. If you explicitly invoke CAF in your program, you can use the CAF connection functions to control the state of the connection.

Example JCL for invoking CAF

The following sample JCL shows how to use CAF in a batch (non-TSO) environment. The DSNTRACE statement in this example is optional.
//jobname      JOB      z/OS_jobcard_information
//CAFJCL       EXEC     PGM=CAF_application_program
//STEPLIB      DD       DSN=application_load_library
//             DD       DSN=DB2_load_library
 
⋮
 
//SYSPRINT     DD       SYSOUT=*
//DSNTRACE     DD       SYSOUT=*
//SYSUDUMP     DD       SYSOUT=*

Example of assembler code that invokes CAF

The following examples show parts of a sample assembler program that uses CAF. They demonstrate the basic techniques for making CAF calls, but do not show the code and z/OS® macros needed to support those calls. For example, many applications need a two-task structure so that attention-handling routines can detach connected subtasks to regain control from Db2. This structure is not shown in the following code examples. Also, these code examples assume the existence of a WRITE macro. Wherever this macro is included in the example, substitute code of your own. You must decide what you want your application to do in those situations; you probably do not want to write the error messages shown.

Example of loading and deleting the CAF language interface

The following code segment shows how an application can load entry points DSNALI and DSNHLI2 for the CAF language interface. Storing the entry points in variables LIALI and LISQL ensures that the application has to load the entry points only once. When the module is done with Db2, you should delete the entries.

****************************** GET LANGUAGE INTERFACE ENTRY ADDRESSES
         LOAD  EP=DSNALI          Load the CAF service request EP
         ST    R0,LIALI           Save this for CAF service requests
         LOAD  EP=DSNHLI2         Load the CAF SQL call Entry Point
         ST    R0,LISQL           Save this for SQL calls
*        .
*        .     Insert connection service requests and SQL calls here
*        .
         DELETE EP=DSNALI         Correctly maintain use count
         DELETE EP=DSNHLI2        Correctly maintain use count

Example of connecting to Db2 with CAF

The following example code shows how to issue explicit requests for certain actions, such as CONNECT, OPEN, CLOSE, DISCONNECT, and TRANSLATE, and uses the CHEKCODE subroutine to check the return reason codes from CAF.

****************************** CONNECT ********************************
         L     R15,LIALI          Get the Language Interface address
         MVC   FUNCTN,CONNECT     Get the function to call
         CALL  (15),(FUNCTN,SSID,TECB,SECB,RIBPTR),VL,MF=(E,CAFCALL)
         BAL   R14,CHEKCODE       Check the return and reason codes
         CLC   CONTROL,CONTINUE   Is everything still OK
         BNE   EXIT               If CONTROL not 'CONTINUE', stop loop
         USING R8,RIB             Prepare to access the RIB
         L     R8,RIBPTR          Access RIB to get DB2 release level
         CLC   RIBREL,RIBR999     DB2 V10 or later?          
         BE    USERELX            If RIBREL = '999', use RIBRELX
         WRITE 'The current DB2 release level is' RIBREL
         B     OPEN               Continue with signon  
         USERELX  WRITE 'The current DB2 release level is' RIBRELX
 
****************************** OPEN ***********************************
OPEN     L     R15,LIALI          Get the Language Interface address
         MVC   FUNCTN,OPEN        Get the function to call
         CALL  (15),(FUNCTN,SSID,PLAN),VL,MF=(E,CAFCALL)
         BAL   R14,CHEKCODE       Check the return and reason codes
 
****************************** SQL ************************************
*              Insert your SQL calls here.  The DB2 Precompiler
*              generates calls to entry point DSNHLI.  You should
*              specify the precompiler option ATTACH(CAF), or code
*              a dummy entry point named DSNHLI to intercept
*              all SQL calls. A dummy DSNHLI is shown below.
****************************** CLOSE **********************************
         CLC   CONTROL,CONTINUE   Is everything still OK?
         BNE   EXIT               If CONTROL not 'CONTINUE', shut down
         MVC   TRMOP,ABRT         Assume termination with ABRT parameter
         L     R4,SQLCODE         Put the SQLCODE into a register
         C     R4,CODE0           Examine the SQLCODE
         BZ    SYNCTERM           If zero, then CLOSE with SYNC parameter
         C     R4,CODE100         See if SQLCODE was 100
         BNE   DISC               If not 100, CLOSE with ABRT parameter
SYNCTERM MVC   TRMOP,SYNC         Good code, terminate with SYNC parameter
DISC     DS    0H                 Now build the CAF parmlist
         L     R15,LIALI          Get the Language Interface address
         MVC   FUNCTN,CLOSE       Get the function to call
         CALL  (15),(FUNCTN,TRMOP),VL,MF=(E,CAFCALL)
         BAL   R14,CHEKCODE       Check the return and reason codes
 
****************************** DISCONNECT *****************************
         CLC   CONTROL,CONTINUE   Is everything still OK
         BNE   EXIT               If CONTROL not 'CONTINUE', stop loop
         L     R15,LIALI          Get the Language Interface address
         MVC   FUNCTN,DISCON      Get the function to call
         CALL  (15),(FUNCTN),VL,MF=(E,CAFCALL)
         BAL   R14,CHEKCODE       Check the return and reason codes

This example code does not show a task that waits on the Db2 termination ECB. If you want such a task, you can code it by using the z/OS WAIT macro to monitor the ECB. You probably want this task to detach the sample code if the termination ECB is posted. That task can also wait on the Db2 startup ECB. This sample waits on the startup ECB at its own task level.

This example code assumes that the variables in the following table are already set:
Table 1. Variables that preceding example assembler code assumes are set
Variable Usage
LIALI The entry point that handles Db2 connection service requests.
LISQL The entry point that handles SQL calls.
SSID The Db2 subsystem identifier.
TECB The address of the Db2 termination ECB.
SECB The address of the Db2 startup ECB.
RIBPTR A fullword that CAF sets to contain the RIB address.
PLAN The plan name to use in the OPEN call.
CONTROL This variable is used to shut down processing because of unsatisfactory return or reason codes. The CHECKCODE subroutine sets this value.
CAFCALL List-form parameter area for the CALL macro.

Example of checking return codes and reason codes when using CAF

The following example code illustrates a way to check the return codes and the Db2 termination ECB after each connection service request and SQL call. The routine sets the variable CONTROL to control further processing within the module.
***********************************************************************
* CHEKCODE PSEUDOCODE                                                 *
***********************************************************************
*IF TECB is POSTed with the ABTERM or FORCE codes
*  THEN
*    CONTROL = 'SHUTDOWN'
*    WRITE 'DB2 found FORCE or ABTERM, shutting down'
*  ELSE                           /* Termination ECB was not POSTed  */
*    SELECT (RETCODE)             /* Look at the return code         */
*      WHEN (0) ;                 /* Do nothing; everything is OK    */
*      WHEN (4) ;                 /* Warning                         */
*        SELECT (REASCODE)        /* Look at the reason code         */
*          WHEN ('00C10824'X)     /* Ready for another CAF call      */
*            CONTROL = 'RESTART'  /* Start over, from the top        */
*          OTHERWISE
*            WRITE 'Found unexpected R0 when R15 was 4'
*            CONTROL = 'SHUTDOWN'
*        END INNER-SELECT
*      WHEN (8,12)                /* Connection failure              */
*        SELECT (REASCODE)        /* Look at the reason code         */
*          WHEN ('00C10831'X)     /* DB2 / CAF release level mismatch*/
*            WRITE 'Found a mismatch between DB2 and CAF release levels'
*          WHEN ('00F30002'X,     /* These mean that DB2 is down but */
*                '00F30012'X)     /* will POST SECB when up again    */
*            DO
*              WRITE 'DB2 is unavailable. I'll tell you when it is up.'
*              WAIT SECB          /* Wait for DB2 to come up         */
*              WRITE 'DB2 is now available.'
*            END
*          /**********************************************************/
*          /* Insert tests for other DB2 connection failures here.   */
*          /* CAF Externals Specification lists other codes you can  */
*          /* receive.  Handle them in whatever way is appropriate   */
*          /* for your application.                                  */
*          /**********************************************************/
*          OTHERWISE              /* Found a code we're not ready for*/
*            WRITE 'Warning: DB2 connection failure. Cause unknown'
*            CALL DSNALI ('TRANSLATE',SQLCA) /* Fill in SQLCA       */
*            WRITE SQLCODE and SQLERRM
*        END INNER-SELECT
*      WHEN (200)
*        WRITE 'CAF found user error. See DSNTRACE data set'
*      WHEN (204)
*        WRITE 'CAF system error. See DSNTRACE data set'
*      OTHERWISE
*        CONTROL = 'SHUTDOWN'
*        WRITE 'Got an unrecognized return code'
*    END MAIN SELECT
*    IF (RETCODE > 4) THEN         /* Was there a connection problem?*/
*      CONTROL = 'SHUTDOWN'
* END CHEKCODE
***********************************************************************
* Subroutine CHEKCODE checks return codes from DB2 and Call Attach.
* When CHEKCODE receives control, R13 should point to the caller's
* save area.
***********************************************************************
CHEKCODE DS    0H
         STM   R14,R12,12(R13)    Prolog
         ST    R15,RETCODE        Save the return code
         ST    R0,REASCODE        Save the reason code
         LA    R15,SAVEAREA       Get save area address
         ST    R13,4(,R15)        Chain the save areas
         ST    R15,8(,R13)        Chain the save areas
         LR    R13,R15            Put save area address in R13
*        ********************* HUNT FOR FORCE OR ABTERM ***************
         TM    TECB,POSTBIT       See if TECB was POSTed
         BZ    DOCHECKS           Branch if TECB was not POSTed
         CLC   TECBCODE(3),QUIESCE   Is this "STOP DB2 MODE=FORCE"
         BE    DOCHECKS           If not QUIESCE, was FORCE or ABTERM
         MVC   CONTROL,SHUTDOWN   Shutdown
         WRITE 'Found found FORCE or ABTERM, shutting down'
         B     ENDCCODE           Go to the end of CHEKCODE
DOCHECKS DS    0H                 Examine RETCODE and REASCODE
*        ********************* HUNT FOR 0 *****************************
         CLC   RETCODE,ZERO       Was it a zero?
         BE    ENDCCODE           Nothing to do in CHEKCODE for zero
*        ********************* HUNT FOR 4 *****************************
         CLC   RETCODE,FOUR       Was it a 4?
         BNE   HUNT8              If not a 4, hunt eights
         CLC   REASCODE,C10831    Was it a release level mismatch?
         BNE   HUNT824            Branch if not an 831
         WRITE 'Found a mismatch between DB2 and CAF release levels'
         B     ENDCCODE           We are done. Go to end of CHEKCODE
HUNT824  DS    0H                 Now look for 'CAF reset' reason code
         CLC   REASCODE,C10824    Was it 4? Are we ready to restart?
         BNE   UNRECOG            If not 824, got unknown code
         WRITE 'CAF is now ready for more input'
         MVC   CONTROL,RESTART    Indicate that we should re-CONNECT
         B     ENDCCODE           We are done. Go to end of CHEKCODE
UNRECOG  DS    0H
         WRITE 'Got RETCODE = 4 and an unrecognized reason code'
         MVC   CONTROL,SHUTDOWN   Shutdown, serious problem
         B     ENDCCODE           We are done. Go to end of CHEKCODE
*        ********************* HUNT FOR 8 *****************************
HUNT8    DS    0H
         CLC   RETCODE,EIGHT      Hunt return code of 8
         BE    GOT8OR12
         CLC   RETCODE,TWELVE     Hunt return code of 12
         BNE   HUNT200
GOT8OR12 DS    0H                 Found return code of 8 or 12
         WRITE 'Found RETCODE of 8 or 12'
         CLC   REASCODE,F30002    Hunt for X'00F30002'
         BE    DB2DOWN
         CLC   REASCODE,F30012    Hunt for X'00F30012'
         BE    DB2DOWN
         WRITE 'DB2 connection failure with an unrecognized REASCODE'
         CLC   SQLCODE,ZERO       See if we need TRANSLATE
         BNE   A4TRANS            If not blank, skip TRANSLATE
*        ********************* TRANSLATE unrecognized RETCODEs ********
         WRITE 'SQLCODE 0 but R15 not, so TRANSLATE to get SQLCODE'
         L     R15,LIALI          Get the Language Interface address
         CALL  (15),(TRANSLAT,SQLCA),VL,MF=(E,CAFCALL)
         C     R0,C10205          Did the TRANSLATE work?
         BNE   A4TRANS            If not C10205, SQLERRM now filled in
         WRITE 'Not able to TRANSLATE the connection failure'
         B     ENDCCODE           Go to end of CHEKCODE
A4TRANS  DS    0H                 SQLERRM must be filled in to get here
*        Note: your code should probably remove the X'FF'
*        separators and format the SQLERRM feedback area.
*        Alternatively, use DB2 Sample Application DSNTIAR
*        to format a message.
         WRITE 'SQLERRM is:' SQLERRM
         B     ENDCCODE           We are done. Go to end of CHEKCODE
DB2DOWN  DS    0H                 Hunt return code of 200
         WRITE 'DB2 is down and I will tell you when it comes up'
         WAIT  ECB=SECB           Wait for DB2 to come up
         WRITE 'DB2 is now available'
         MVC   CONTROL,RESTART    Indicate that we should re-CONNECT
         B     ENDCCODE
*        ********************* HUNT FOR 200 ***************************
HUNT200  DS    0H                 Hunt return code of 200
         CLC   RETCODE,NUM200     Hunt 200
         BNE   HUNT204
         WRITE 'CAF found user error, see DSNTRACE data set'
         B     ENDCCODE           We are done. Go to end of CHEKCODE
*        ********************* HUNT FOR 204 ***************************
HUNT204  DS    0H                 Hunt return code of 204
         CLC   RETCODE,NUM204     Hunt 204
         BNE   WASSAT             If not 204, got strange code
         WRITE 'CAF found system error, see DSNTRACE data set'
         B     ENDCCODE           We are done. Go to end of CHEKCODE
*        ********************* UNRECOGNIZED RETCODE *******************
WASSAT   DS    0H
         WRITE 'Got an unrecognized RETCODE'
         MVC   CONTROL,SHUTDOWN   Shutdown
         BE    ENDCCODE           We are done. Go to end of CHEKCODE
ENDCCODE DS    0H                 Should we shut down?
         L     R4,RETCODE         Get a copy of the RETCODE
         C     R4,FOUR            Have a look at the RETCODE
         BNH   BYEBYE             If RETCODE <= 4 then leave CHEKCODE
         MVC   CONTROL,SHUTDOWN   Shutdown
BYEBYE   DS    0H                 Wrap up and leave CHEKCODE
         L     R13,4(,R13)        Point to caller's save area
         RETURN (14,12)           Return to the caller

Example of invoking CAF when you do not specify the precompiler option ATTACH(CAF)

Each of the four Db2 attachment facilities contains an entry point named DSNHLI. When you use CAF but do not specify the precompiler option ATTACH(CAF), SQL statements result in BALR instructions to DSNHLI in your program. To find the correct DSNHLI entry point without including DSNALI in your load module, code a subroutine with entry point DSNHLI that passes control to entry point DSNHLI2 in the DSNALI module. DSNHLI2 is unique to DSNALI and is at the same location in DSNALI as DSNHLI. DSNALI uses 31-bit addressing. If the application that calls this intermediate subroutine uses 24-bit addressing, this subroutine should account for the difference.

In the following example, LISQL is addressable because the calling CSECT used the same register 12 as CSECT DSNHLI. Your application must also establish addressability to LISQL.

***********************************************************************
* Subroutine DSNHLI intercepts calls to LI EP=DSNHLI
***********************************************************************
         DS    0D
DSNHLI   CSECT                    Begin CSECT
         STM   R14,R12,12(R13)    Prologue
         LA    R15,SAVEHLI        Get save area address
         ST    R13,4(,R15)        Chain the save areas
         ST    R15,8(,R13)        Chain the save areas
         LR    R13,R15            Put save area address in R13
         L     R15,LISQL          Get the address of real DSNHLI
         BASSM R14,R15            Branch to DSNALI to do an SQL call
*                                 DSNALI is in 31-bit mode, so use
*                                 BASSM to assure that the addressing
*                                 mode is preserved.
         L     R13,4(,R13)        Restore R13 (caller's save area addr)
         L     R14,12(,R13)       Restore R14 (return address)
         RETURN (1,12)            Restore R1-12, NOT R0 and R15 (codes)

Example of variable declarations when using CAF

The following example code shows declarations for some of the variables that were used in the previous subroutines.
****************************** VARIABLES ******************************
SECB     DS    F                  DB2 Startup ECB
TECB     DS    F                  DB2 Termination ECB
LIALI    DS    F                  DSNALI Entry Point address
LISQL    DS    F                  DSNHLI2 Entry Point address
SSID     DS    CL4                DB2 Subsystem ID.  CONNECT parameter
PLAN     DS    CL8                DB2 Plan name.  OPEN parameter
TRMOP    DS    CL4                CLOSE termination option (SYNC|ABRT)
FUNCTN   DS    CL12               CAF function to be called
RIBPTR   DS    F                  DB2 puts Release Info Block addr here
RETCODE  DS    F                  Chekcode saves R15 here
REASCODE DS    F                  Chekcode saves R0 here
CONTROL  DS    CL8                GO, SHUTDOWN, or RESTART
SAVEAREA DS  18F                  Save area for CHEKCODE
****************************** CONSTANTS ******************************
SHUTDOWN DC    CL8'SHUTDOWN'      CONTROL value: Shutdown execution
RESTART  DC    CL8'RESTART '      CONTROL value: Restart execution
CONTINUE DC    CL8'CONTINUE'      CONTROL value: Everything OK, cont
CODE0    DC    F'0'               SQLCODE of 0
CODE100  DC    F'100'             SQLCODE of 100
QUIESCE  DC    XL3'000008'        TECB postcode: STOP DB2 MODE=QUIESCE
CONNECT  DC    CL12'CONNECT     ' Name of a CAF service. Must be CL12!
OPEN     DC    CL12'OPEN        ' Name of a CAF service. Must be CL12!
CLOSE    DC    CL12'CLOSE       ' Name of a CAF service. Must be CL12!
DISCON   DC    CL12'DISCONNECT  ' Name of a CAF service. Must be CL12!
TRANSLAT DC    CL12'TRANSLATE   ' Name of a CAF service. Must be CL12!
SYNC     DC    CL4'SYNC'          Termination option (COMMIT)
ABRT     DC    CL4'ABRT'          Termination option (ROLLBACK)
****************************** RETURN CODES (R15) FROM CALL ATTACH ****
ZERO     DC    F'0'               0
FOUR     DC    F'4'               4
EIGHT    DC    F'8'               8
TWELVE   DC    F'12'              12  (Call Attach return code in R15)
NUM200   DC    F'200'             200 (User error)
NUM204   DC    F'204'             204 (Call Attach system error)
****************************** REASON CODES (R00) FROM CALL ATTACH ****
C10205   DC    XL4'00C10205'      Call attach could not TRANSLATE
C10831   DC    XL4'00C10831'      Call attach found a release mismatch
C10824   DC    XL4'00C10824'      Call attach ready for more input
F30002   DC    XL4'00F30002'      DB2 subsystem not up
F30011   DC    XL4'00F30011'      DB2 subsystem not up
F30012   DC    XL4'00F30012'      DB2 subsystem not up
F30025   DC    XL4'00F30025'      DB2 is stopping (REASCODE)
*
*        Insert more codes here as necessary for your application
*
****************************** SQLCA and RIB **************************
    EXEC SQL INCLUDE SQLCA
         DSNDRIB                  Get the DB2 Release Information Block
****************************** CALL macro parm list *******************
CAFCALL  CALL  ,(*,*,*,*,*,*,*,*,*),VL,MF=L