TDSETSPT

Description

Sets tracing on or off for a specified transaction.

Syntax

COPY SYGWCOB.
01 IHANDLE               PIC S9(9)  USAGE COMP SYNC.
01 RETCODE               PIC S9(9)  USAGE COMP SYNC.
01 TRACE-STATUS          PIC S9(9)  USAGE COMP SYNC.
01 TRACE-OPTIONS         PIC S9(9)  USAGE COMP SYNC.
01 TRANSACTION-ID        PIC X(n).
01 TRANSACTION-ID-LENGTH PIC S9(9)  USAGE COMP SYNC.
CALL 'TDSETSPT' USING IHANDLE, RETCODE, TRACE-STATUS,
                TRACE-OPTIONS, TRANSACTION-ID, 
                TRANSACTION-ID-LENGTH. 

Parameters

IHANDLE

(I) A transaction-wide structure that contains information used to set up the Gateway-Library environment. This must be the same IHANDLE specified in the program’s initial TDINIT call. It corresponds to the context structure 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-36.

TRACE-STATUS

(I) Trace indicator for the specified transaction. This is a Boolean value that turns tracing on or off for the specified transaction.

Assign this argument one of the following values:

TDS-TRUE (1)

Turn on tracing for this transaction.

TDS-FALSE (0)

Turn off tracing for this transaction.

TRACE-OPTIONS

(I) Type of tracing to be enabled for the specified transaction. Assign this argument one of the following values:

TDS-SPT-API-TRACE (0x08)

Trace all Gateway-Library calls.

TDS-SPT-ERRLOG (0x02)

Enable error log recording.

TDS-SPT-TDS-DATA (0x01)

Enable TDS packet-tracing recording.

TRANSACTION-ID

(I) Mainframe transaction identifier of the affected transaction.

Under CICS: This is the TRANSID from the CICS Program Control Table (PCT).

Under IMS TM: This is the transaction name defined when the system is generated.

Under MVS: This is the APPC transaction name defined in the transaction profile.

TRANSACTION-ID-LENGTH

(I) Length of the TRANSACTION-ID.

For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes. This value is returned by TDINFSPT.

Under CICS: For CICS Version 1.7, this value is always 4 or less. For later versions, it is the actual length of the transaction ID, which can be greater than 4.

Under IMS TM: This value is always 8 or less.

Under MVS: This is the APPC transaction name defined in the transaction profile. This value is normally 8 or less.

Returns

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

Table 3-36: TDSETSPT return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-DUPLICATE-ENTRY (-9)

Duplicate column description. You attempted to describe the same column twice with a TDESCRIB statement. The operation failed.

TDS-ENTRY-NOT-FOUND (-8)

The specified column number, transaction number, or parameter does not exist.

TDS-INVALID-IHANDLE (-19)

Invalid IHANDLE specification. Error in specifying a value for the IHANDLE argument.

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-STATUS (-174)

Invalid status value. The value entered in the STATUS field is invalid.

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 shows how to use TDINFLOG at the beginning of a program to determine which types of tracing are currently enabled and TDSETSPT at the end of a program. 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.
 
 *    Turn on local tracing if not on globally or locally
            CALL 'TDINFLOG' USING GWL-INIT-HANDLE, GWL-RC,
                                  GWL-INFLOG-GLOBAL,
                                  GWL-INFLOG-API,
                                  GWL-INFLOG-TDS-HEADER,
                                  GWL-INFLOG-TDS-DATA,
                                  GWL-INFLOG-TRACE-ID,
                                  GWL-INFLOG-FILENAME,
                                  GWL-INFLOG-TOTAL-RECS.
 
            IF  GWL-INFLOG-GLOBAL NOT = TDS-TRACE-ALL-RPCS
            AND GWL-INFLOG-GLOBAL NOT = TDS-TRACE-SPECIFIC-RPCS THEN
                MOVE 1 TO TRACING-SET-SW
                PERFORM LOCAL-TRACING
            END-IF.
 
       *    Accept client request
 
            CALL 'TDACCEPT' USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,
                                  SNA-CONNECTION-NAME,
                                  SNA-SUBC.
    
 *----------------------------------------------------------------
 LOCAL-TRACING.
 *----------------------------------------------------------------
      CALL 'TDSETSPT' USING GWL-INIT-HANDLE, GWL-RC,
                            TRACING-SET-SW,
                            GWL-SETSPT-TRACE-LEVEL, 
                            GWL-SETSPT-RPC-NAME,
                             GWL-SETSPT-RPC-NAME-L.

Usage

See also

Related functions