TDINFLOG

Description

Determines what types of mainframe server tracing have been set.

Syntax

COPY SYGWCOB.
01 IHANDLE               PIC S9(9) USAGE COMP SYNC.
01 RETCODE               PIC S9(9) USAGE COMP SYNC.
01 GLOBAL-TRACE-FLAG     PIC S9(9) USAGE COMP SYNC.
01 API-TRACE-FLAG        PIC S9(9) USAGE COMP SYNC.
01 TDS-HEADER-TRACE-FLAG PIC S9(9) USAGE COMP SYNC.
01 TDS-DATA-TRACE-FLAG   PIC S9(9) USAGE COMP SYNC.
01 TRACE-ID              PIC S9(9) USAGE COMP SYNC.
01 TRACE-FILENAME        PIC X(8).
01 MAXNUM-TRACE-RECORDS  PIC S9(9) USAGE COMP SYNC.
CALL 'TDINFLOG' USING IHANDLE,RETCODE,GLOBAL-TRACE-FLAG, API-TRACE-FLAG,TDS-HEADER-TRACE-FLAG TDS-DATA-TRACE-FLAG, TRACE-ID,TRACE-FILENAME, MAXNUM-TRACE-RECORDS.

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

GLOBAL-TRACE-FLAG

(O) Global/specific trace indicator. This argument indicates whether tracing is on or off, and whether it is global (traces all transactions) or applies to a specific set of transactions. If tracing is set off, only errors are logged.

The GLOBAL-TRACE-FLAG argument returns one of the following values:

TDS-NO-TRACING (0)

All tracing is off.

TDS-TRACE-ALL-RPCS (1)

Global tracing is on.

TDS-TRACE-SPECIFIC-RPCS (2)

Specific tracing is on.

TDS-TRACE-ERRORS-ONLY (3)

Only errors are logged.

API-TRACE-FLAG

(O) The API tracing on/off indicator. This is a Boolean value that indicates whether tracing is turned on or off for Gateway-Library calls. This argument returns one of the following values:

TDS-TRUE (1)

API tracing is on.

TDS-FALSE (0)

API tracing is off.

TDS-HEADER-TRACE-FLAG

(O) The TDS header tracing on/off indicator. This is a Boolean value that indicates whether tracing is turned on or off for TDS headers. This argument returns one of the following values:

TDS-TRUE (1)

Header tracing is on.

TDS-FALSE (0)

Header tracing is off.

TDS-DATA-TRACE-FLAG

(O) The TDS data tracing on/off indicator. This is a Boolean value that indicates whether tracing is turned on or off for TDS data. This argument returns one of the following values:

TDS-TRUE (1)

Data tracing is on.

TDS-FALSE (0)

Data tracing is off.

TRACE-ID

(O) The trace entry identifier.

Under CICS: This is the tag for the auxiliary file entry.

Under IMS TM and MVS: Leave this field blank. This argument is ignored.

TRACE-FILENAME

(O) Name of the trace/error log.

Under CICS: This is the DATASET name from the CICS File Control Table (FCT) entry that describes the VSAM file used for this log. As installed, this name is SYTDLOG1.

Under IMS TM and MVS: Leave this field blank. IMS TM and MVS ignore this value.

MAXNUM-TRACE-RECORDS

(O) Trace log record limit.

Under CICS: This is the maximum number of records that can be written to this file. A value of -1 indicates the system maximum.

Under IMS TM: The IMS TM system log does not have a limit.

Under MVS: The limit is the amount of space on the log file.

Returns

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

Table 3-14: TDINFLOG 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.

TDS-LOG-ERROR(-258)

Attempt to write to the log file 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. 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