TDINFSPT

Description

Indicates whether tracing is 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-OPTION          PIC S9(9)  USAGE COMP SYNC.
01 TRANSACTION-ID        PIC X(n).
01 TRANSACTION-ID-LENGTH PIC S9(9)  USAGE COMP SYNC.
CALL 'TDINFSPT' USING IHANDLE, RETCODE, TRACE-STATUS,
               TRACE-OPTION, 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-20.

TRACE-STATUS

(O) Variable where the trace indicator for the specified transaction is returned. This is a Boolean value that indicates whether tracing is on or off for the transaction specified in this function.

This argument returns one of the following values:

TDS-TRUE (1)

Tracing is on for this transaction.

TDS-FALSE (0)

Tracing is off for this transaction.

TRACE-OPTION

(O) Variable where the type of tracing enabled for the specified transaction is returned. This argument returns one of the following values:

TDS-SPT-API-TRACE (0x08)

All Gateway-Library calls are traced.

TDS-SPT-ERRLOG (0x02)

Error log recording is enabled.

TDS-SPT-TDS-DATA (0x01)

TDS packet-tracing recording is enabled.

TRANSACTION-ID

(I) Mainframe transaction identifier of the transaction for which the trace status is requested.

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

(O) Variable where the length of the TRANSACTION-ID is returned. For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes.

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

Table 3-20: TDINFSPT return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

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.

Examples

Example 1

The following code fragment illustrates the use of TDINFSPT to determine whether tracing is enabled for a particular transaction. This example is taken from the sample program in Appendix G, “Sample Tracing and Accounting Program” which runs under CICS.

 *----------------------------------------------------------------
  GET-TRACE-STATUS. 
 *----------------------------------------------------------------
 *    Determine whether global tracing is on.
     CALL 'TDINFLOG' USING GWL-INIT-HANDLE, GWL-RC, 
                            GWL-INFLOG-GLOBAL, GWL-INFLOG-API,
                            GWL-INFLOG-HEADER, GWL-INFLOG-DATA,
                            GWL-INFLOG-TRACEID,
                            GWL-INFLOG-FILENAME,
 *    If specific tracing is on, see if it's on for this 
 *    transaction and turn on the tracing flag.
     IF GWL-INFLOG-GLOBAL NOT = TDS-TRACE-SPECIFIC-RPCS  
            GO TO GET-TRACE-STATUS-EXIT 
      END-IF.
     MOVE LENGTH OF WRK-RPC TO WRKLEN1.
     CALL 'TDINFSPT' USING GWL-INIT-HANDLE, GWL-RC, 
                            GWL-INFSPT-STATUS, GWL-INFSPT-OPTIONS,
                            WRK-RPC, WRKLEN1.
     IF GWL-RC NOT = TDS-OK AND 
            GWL-RC NOT = TDS-ENTRY-NOT-FOUND THEN 
            MOVE 'N' TO SEND-DONE-SW 
            MOVE 'TDINFSPT' TO MSG-SRVLIB-FUNC 
            GO TO GET-TRACE-STATUS-EXIT 
      END-IF.
     IF GWL-INFSPT-STATUS = TDS-TRUE THEN 
            MOVE 'Y' TO TRACING-SW 
      END-IF.

Usage

See also

Related functions

Related documents