TDLSTSPT

Description

Lists transactions for which tracing is enabled.

Syntax

COPY SYGWCOB.
01 IHANDLE           PIC S9(9)  USAGE COMP SYNC.
01 RETCODE           PIC S9(9)  USAGE COMP SYNC.
01 TRACE-TABLE-LIST  OCCURS 8 TIMES 
                      PIC X(8).  
CALL 'TDLSTSPT' USING IHANDLE,RETCODE,
                TRACE-TABLE-LIST.

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

TRACE-TABLE-LIST

(O) An array listing the contents of the trace table. Each element of this array, TRANSID-n, returns the transaction ID of a transaction for which specific tracing is currently enabled.

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 of the MVS transaction.

Returns

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

Table 3-23: TDLSTSPT 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 TDLSTSPT to determine which transactions have tracing enabled. It returns the transaction IDs to the caller. This example is taken from the sample program in Appendix G, “Sample Tracing and Accounting Program” which runs under CICS.

*    ------------------------------------------------------------
*    Describe column containing transaction ID. 
*    ------------------------------------------------------------
     MOVE LENGTH OF WRK-TRANID       TO WRKLEN1. 
      MOVE LENGTH OF CN-LSTSPT-TRANID TO WRKLEN2. 
      ADD +1                          TO CTR-COLUMN.
     CALL 'TDESCRIB' USING GWL-PROC, GWL-RC, 
                            CTR-COLUMN, TDSCHAR, 
                            WRKLEN1, WRK-TRANID, 
	TDS-ZERO, TDS-FALSE, 
	TDSCHAR, WRKLEN1, 
	CN-LSTSPT-TRANID, WRKLEN2.
*   ------------------------------------------------------------ 
*   Find out whether specific tracing is on; if not, exit. 
*   ------------------------------------------------------------ 
      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,
                            GWL-INFLOG-RECORDS. 
     IF GWL-INFLOG-GLOBAL NOT = TDS-TRACE-SPECIFIC-RPCS THEN 
     GO TO TDLSTSPT-EXIT 
     END-IF.
*   ------------------------------------------------------------*   Return trace table IDs to client, one item at a time. 
*   -------------------------------------------------------------
     CALL 'TDLSTSPT' USING GWL-INIT-HANDLE, GWL-RC, 
                            GWL-LSTSPT-LIST(1).
     IF GWL-RC NOT = TDS-OK THEN 
           MOVE 'N'           TO SEND-DONE-SW 
           MOVE 'TDLSTSPT'    TO MSG-SRVLIB-FUNC 
           GO TO TDLSTSPT-EXIT 
      END-IF.
     PERFORM VARYING WRK-LSTSPT-SS FROM 1 BY 1
          UNTIL WRK-LSTSPT-SS = 8
          MOVE GWL-LSTSPT-LIST(WRK-LSTSPT-SS) TO WRK-TRANID 
           CALL 'TDSNDROW' USING GWL-PROC, GWL-RC 
           ADD +1 TO CTR-ROWS 
      END-PERFORM.

Usage

See also

Related functions

Related documents