TDINFPGM

Description

Retrieves information about the current client request.

Syntax

COPY SYGWCOB.
01 TDPROC             PIC S9(9)  USAGE COMP SYNC.
01 RETCODE            PIC S9(9)  USAGE COMP SYNC.
01 TDS-VERSION        PIC S9(9)  USAGE COMP SYNC.
01 LONGVAR-TRUNC-FLAG PIC S9(9)  USAGE COMP SYNC.
01 ROW-LIMIT          PIC S9(9)  USAGE COMP SYNC.
01 REMOTE-TRACE-FLAG  PIC S9(9)  USAGE COMP SYNC.
01 USER-CORRELATOR    PIC S9(9)  USAGE COMP SYNC.
01 DB2GW-OPTIONS      PIC S9(9)  USAGE COMP SYNC.
01 DB2GW-PID          PIC X(8).
01 REQUEST-TYPE       PIC S9(9)  USAGE COMP SYNC.
CALL 'TDINFPGM’ USING  TDPROC,RETCODE, TDS-VERSION,
                LONGVAR-TRUNC-FLAG,ROW-LIMIT,
                REMOTE-TRACE-FLAG,
                USER-CORRELATOR,DB2GW-OPTIONS,
                 DB2GW-PID, REQUEST-TYPE.

Parameters

TDPROC

(I) Handle for this client/server connection. This must be the same value specified in the 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-16.

TDS-VERSION

(O) Variable where the version of TDS being used is returned. The version value can be any of the following listed in Table 3-15.

Table 3-15: TDS-VERSION values

TDS-VERSION-20 PIC S9(9) COMP VALUE 512

TDS-VERSION-34 PIC S9(9) COMP VALUE 832

TDS-VERSION-40 PIC S9(9) COMP VALUE 1024

TDS-VERSION-42 PIC S9(9) COMP VALUE 1056

TDS-VERSION-46 PIC S9(9) COMP VALUE 1120

TDS-VERSION-48 PIC S9(9) COMP VALUE 1152

TDS-VERSION-49 PIC S9(9) COMP VALUE 1168

TDS-VERSION-50 PIC S9(9) COMP VALUE 1280

TDS-VERSION-51 PIC S9(9) COMP VALUE 1296

This value must be the same as the version level specified at the client.

LONGVAR-TRUNC-FLAG

(O) Variable where the truncation indicator for TDSLONGVARCHAR fields is returned. It indicates what happens when TDSLONGVARCHAR fields over 255 characters are returned to the client.

One of the following values is returned in this variable:

TDS-TRUE (1)

TDSLONGVARCHAR fields are truncated.

TDS-FALSE (0)

TDSLONGVARCHAR fields are not truncated; an error is returned instead.

If 0 is specified, it is the responsibility of the Gateway-Library programmer to determine what action is taken.

NoteTDSLONGVARCHAR truncation may also be specified at the mainframe during customization. If truncation is set on at either the mainframe or the TRS, truncation occurs.

ROW-LIMIT

This argument is ignored.

REMOTE-TRACE-FLAG

(O) Variable that contains the TRS tracing indicator. This is a Boolean value that indicates whether tracing is on or off at the TRS.

One of the following values is returned in this variable:

TDS-TRUE (1)

TRS tracing is on.

TDS-FALSE (0)

TRS tracing is off.

USER-CORRELATOR

(I) Information argument. You can use this argument for any purpose.

DB2GW-OPTIONS

This argument is ignored.

DB2GW-PID

This argument is ignored.

REQUEST-TYPE

(O) Variable where the type of client request is indicated. One of the following values is returned:

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.

TDGETREQ 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.

Returns

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

Table 3-16: TDINFPGM return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

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.

Examples

Example 1

The following code fragment illustrates the use of TDINFPGM to determine what kind of request was received. This example is taken from the sample program in Appendix C, “Sample Language Application for CICS.”

*    Establish gateway environment.
     CALL 'TDINIT' USING DFHEIBLK, GWL-RC, GWL-INIT-HANDLE.
*    Accept client request
 
            CALL 'TDACCEPT' USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,
                                  SNA-CONNECTION-NAME,
                                  SNA-SUBC.
 
       *    Ensure kicked off via language request
       *    (this could be handled more reasonably by TDRESULT)
 
            CALL 'TDINFPGM' USING GWL-PROC, GWL-RC,
                                  GWL-INFPGM-TDS-VERSION,
                                  GWL-INFPGM-LONGVAR,
                                  GWL-INFPGM-ROW-LIMIT,
                                  GWL-INFPGM-REMOTE-TRACE,
                                  GWL-INFPGM-CORRELATOR,
                                  GWL-INFPGM-DB2GW-OPTION,
                                  GWL-INFPGM-DB2GW-PID,
                                  GWL-INFPGM-TYPE-RPC.
 
            IF GWL-INFPGM-TYPE-RPC NOT = TDS-START-SQL
                MOVE MSG-NOT-LANG           TO MSG-TEXT
                MOVE LENGTH OF MSG-NOT-LANG TO MSG-TEXT-L
                PERFORM SEND-ERROR-MESSAGE
                GO TO END-PROGRAM
            END-IF.

Usage

See also

Related documents