TDGETREQ

Description

Accepts the next request in a long-running transaction.

Syntax

COPY SYGWCOB.
01   TDPROC       PIC S9(9)  USAGE COMP SYNC.
01   RETCODE      PIC S9(9)  USAGE COMP SYNC.
01   WAIT-OPTION  PIC S9(9)  USAGE COMP SYNC.
01   REQUEST-TYPE PIC S9(9)  USAGE COMP SYNC.
01   TRAN-NAME    PIC X(30).
CALL 'TDGETREQ' 
USING TDPROC, RETCODE, WAIT-OPTION
REQUEST-TYPE, TRAN-NAME.

Parameters

TDPROC

(I) Handle for this client/server connection. This must be the same value specified in this associated TDACCEPT call. The TDPROC handle corresponds to the connection and command handles in Open Client Client-Library.

RETCODE

(O) Variable where the result of function execution is returned. Its value is one of the codes listed in Table 3-9.

WAIT-OPTION

(I) Wait/do not wait indicator. Indicates what the application should do after a TDGETREQ if no request is present: (1) wait for a new request to arrive, or (2) terminate immediately.

Assign this argument one of the following values:

TDS-TRUE (1)

Wait for input.

TDS-FALSE (0)

Do not wait for input.

Under CICS and MVS: Sybase recommends always coding TDS-FALSE. Coding TDS-FALSE ends the transaction and frees resources if there is nothing left to do. Coding TDS-TRUE causes the transaction to wait.

Under IMS TM: The WAIT-OPTION tells the transaction what to do when the message queue is empty. This will be to wait for another request to appear on the queue, or end the transaction.

NoteTo use TDGETREQ properly under the IMS TM implicit API, the transaction must be a WPI transaction, or the message region that the transaction runs in must have PWFI=Y (Pseudo-Wait-For-Input) specified.

REQUEST-TYPE

(O) Type of request to be accepted. Returns one of the following values:

TDS-LANGUAGE-EVENT (1)

Current request is a language request.

TDS-RPC-EVENT (3)

Current request is an RPC.

TDS-DYNAMIC-EVENT (4)

Current request is a dynamic SQL request.

TDS-CURSOR-EVENT (5)

Current request is a cursor request.

TDINFPGM and TDINFRPC also return this information.

NoteThese are new values. The old values (TDS-START-SQL and TDS-START-RPC) still work, but you should use the new values from now on.

TRAN-NAME

(O) Variable where the name of the current CICS, MVS or IMS TM transaction is returned.

Returns

The RETCODE argument can contain any of the return values listed in Table 3-9.

Table 3-9: TDGETREQ return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CONNECTION-FAILED (-4998)

Connection abended. The client/server connection abnormally ended (for example, the LU 6.2 session crashed or the remote transaction abended).

TDS-CONNECTION-TERMINATED (-4997)

Connection closed. The remote partner closed (deallocated) the client/server connection.

TDS-INVALID-PARAMETER (-4)

Invalid parameter value. The value assigned to one or more of the arguments supplied in the call is not valid. The operation failed.

TDS-INVALID-TDPROC (-18)

Error in specifying a value for the TDPROC argument.

TDS-SOS (-257)

Memory shortage. The host subsystem was unable to allocate enough memory for the control block that Gateway-Library tried to create. The operation failed.

Examples

Example 1

The following code fragment illustrates the use of TDSNDDON and TDGETREQ in a Gateway-Library long-running transaction using the IMS TM explicit API. This example is taken from the sample program in Appendix E, “Sample RPC Application for IMS TM (Explicit).”

*----------------------------------------------------------------
  SEND ROWS TO CLIENT, MOVE ZEROES TO CTR-ROWS. 
*----------------------------------------------------------------

      IF PARM-NR-ROWS = ZEROES THEN                                               
MOVE ‘Y’ TO ALL-DONE-SW                                      
     ELSE                                                             
         PERFORM SEND-ROWS                                                
           UNTIL ALL-DONE OR CTR-ROWS >= PARM-NR-ROWS.
      IF SEND-DONE-OK                                                  
           MOVE TDS-DONE-COUNT TO WRK-DONE-STATUS                       
      ELSE                                                             
           MOVE TDS-DONE-ERROR TO WRK-DONE-STATUS                       
           MOVE ZERO              TO CTR-ROWS                              
       END-IF.
SEND-DONE.
      IF PARM-NR-ROWS = ZEROES THEN                                    
                MOVE TDS-ENDRPC TO GWL-SEND-DONE                             
       ELSE                                                             
                MOVE TDS-ENDREPLY TO GWL-SEND-DONE.
*----------------------------------------------------------------
  ISSUE SEND DONE TO CLIENT
*----------------------------------------------------------------
      CALL ‘TDSNDDON’ USING GWL-PROC, GWL-RC,
                                WRK-DONE-STATUS,
                                CTR-ROWS,
                                TDS-ZERO,
                                GWL-SEND-DONE.
 
[check return code]

      IF PARM-NR-ROWS = ZEROES THEN
            PERFORM FREE-ALL-STORAGE
       GOBACK.
*----------------------------------------------------------------
  GET NEXT CLIENT REQUEST
*----------------------------------------------------------------
      MOVE TDS-TRUE TO GWL-WAIT-OPTION.                                
      MOVE ZEROES TO GWL-REQ-TYPE.                                     
      MOVE SPACES TO GWL-RPC-NAME.                                     
      CALL ‘TDGETREQ’ USING GWL-PROC, GWL-RC, GWL-WAIT-OPTION
                                GWL-REQ-TYPE, GWL-RPC-NAME. 
[check return code]

      PERFORM FREE-ALL-STORAGE.
      GOBACK.                                                                                                                                                                                                             
  

Example 2

The following code fragment illustrates the use of TDSNDDON and TDGETREQ in a Gateway-Library transaction using the IMS TM implicit API. This example is taken from the sample program in Appendix D, “Sample RPC Application for IMS TM (Implicit).”

*----------------------------------------------------------------
  SEND-ROWS 
*--------------------------------------------------------------- 
     PERFORM FETCH-AND-SEND-ROWS 
           UNTIL ALL-DONE.
 	FINISH-REPLY.

     CALL ‘TDSNDDON’ USING GWL-PROC, GWL-RC, 
                                WRK-DONE-STATUS, CTR-ROWS, 
                                TDS-ZERO, TDS-ENDRPC. 

[check return code]

 *    ------------------------------------------------------------
 *    Get next client request 
 *    ------------------------------------------------------------
      MOVE TDS-TRUE TO GWL-WAIT-OPTION. 
      MOVE ZEROES TO GWL-REQ-TYPE. 
      MOVE SPACES TO GWL-RPC-NAME.
      CALL ‘TDGETREQ’ USING GWL-PROC, GWL-RC, GWL-WAIT-OPTION,
                            GWL-REQ-TYPE, GWL-RPC-NAME.
     EVALUATE GWL-RC 
            WHEN ZEROES 
               GO TO READ-IN-USER-PARM 
            WHEN TDS-RESULTS-COMPLETE 
               PERFORM FREE-ALL-STORAGE 
            WHEN TDS-CONNECTION-TERMINATED 
               PERFORM FREE-ALL-STORAGE 
            WHEN OTHER 
               MOVE ‘TDGETREQ’ TO CALL-ERROR 
               PERFORM DISPLAY-CALL-ERROR 
      END-EVALUATE.

Usage

Note IMS TM Users: Transactions running under the IMS TM implicit API do not support true long-running transactions. See “For IMS TM users” in this section for IMS TM-specific information.


For IMS TM users

See also

Related functions

Related topics