TDINFACT

Description

Retrieves information about Gateway-Library accounting.

Syntax

COPY SYGWCOB.
01 IHANDLE             PIC S9(9)  USAGE COMP SYNC.
01 RETCODE             PIC S9(9)  USAGE COMP SYNC.
01 ACCOUNTING-FLAG     PIC S9(4)  USAGE COMP SYNC.
01 ACCOUNTING-FILENAME PIC X(8)   VALUE IS SPACES.
01 MAXNUM-ACCT-RECORDS PIC 9(9)   USAGE COMP SYNC.
CALL 'TDINFACT’ USING IHANDLE, RETCODE, ACCOUNTING-FLAG, ACCOUNTING-FILENAME MAXNUM-ACCT-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-12.

ACCOUNTING-FLAG

(O) Accounting on/off indicator. This argument returns one of the following values:

TDS-TRUE (1)

Accounting is on.

TDS-FALSE (0)

Accounting is off.

ACCOUNTING-FILENAME

(O) Variable where the name of the accounting log is returned.

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

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

MAXNUM-ACCT-RECORDS

(O) Accounting log record limit.

Under CICS: This is the maximum number of records to be allocated for this accounting file. A value of -1 indicates the system maximum.

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

Under MVS: Use -1. The size of the log is determined by the space allocated to the sequential file used as the MVS log.

Returns

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

Table 3-12: TDINFACT 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 processes a request for accounting information and returns that information to the client. This example is based on the sample program in Appendix G, “Sample Tracing and Accounting Program” which runs under CICS.

 *---------------------------------------------------------------- 
  TDINFACT. 
 *---------------------------------------------------------------- 
     MOVE LENGTH OF GWL-INFACT-STATUS  TO WRKLEN1. 
     MOVE LENGTH OF CN-INFACT-STATUS   TO WRKLEN2. 
     ADD +1                            TO CTR-COLUMN. 
     MOVE 'TDESCRIB'                   TO MSG-SRVLIB-FUNC. 
     CALL 'TDESCRIB' USING GWL-PROC, GWL-RC, CTR-COLUMN, TDSINT4, 
                            WRKLEN1, GWL-INFACT-STATUS, TDS-ZERO, 
                            TDS-FALSE, TDSINT4, WRKLEN1, 
                            CN-INFACT-STATUS, WRKLEN2. 
     IF GWL-RC NOT = TDS-OK THEN 
            MOVE 'N' TO SEND-DONE-SW 
            GO TO TDINFACT-EXIT 
      END-IF. 
     MOVE LENGTH OF GWL-INFACT-FILENAME TO WRKLEN1. 
      MOVE LENGTH OF CN-INFACT-FILENAME  TO WRKLEN2. 
      ADD +1                             TO CTR-COLUMN. 
     CALL 'TDESCRIB' USING GWL-PROC, GWL-RC, CTR-COLUMN, TDSCHAR, 
                            WRKLEN1, GWL-INFACT-FILENAME, 
                            TDS-ZERO, TDS-FALSE, TDSCHAR, WRKLEN1, 
                            CN-INFACT-FILENAME, WRKLEN2. 
     IF GWL-RC NOT = TDS-OK THEN 
            MOVE 'N' TO SEND-DONE-SW 
            GO TO TDINFACT-EXIT 
      END-IF. 
     MOVE LENGTH OF GWL-INFACT-RECORDS  TO WRKLEN1. 
      MOVE LENGTH OF CN-INFACT-RECORDS   TO WRKLEN2. 
      ADD +1                             TO CTR-COLUMN. 
     CALL 'TDESCRIB' USING GWL-PROC, GWL-RC, CTR-COLUMN, TDSINT4, 
                            WRKLEN1, GWL-INFACT-RECORDS, TDS-ZERO, 
                            TDS-FALSE, TDSINT4, WRKLEN1, 
                            CN-INFACT-RECORDS, WRKLEN2. 
     IF GWL-RC NOT = TDS-OK THEN 
            MOVE 'N' TO SEND-DONE-SW 
            GO TO TDINFACT-EXIT 
      END-IF. 
     CALL 'TDINFACT' USING GWL-INIT-HANDLE, GWL-RC, 
                            GWL-INFACT-STATUS, 
                            GWL-INFACT-FILENAME, 
                            GWL-INFACT-RECORDS. 
     IF GWL-RC NOT = TDS-OK THEN 
            MOVE 'N'        TO SEND-DONE-SW 
            MOVE 'TDINFACT' TO MSG-SRVLIB-FUNC 
            GO TO TDINFACT-EXIT 
      END-IF. 
     CALL 'TDSNDROW' USING GWL-PROC, GWL-RC. 
 *---------------------------------------------------------------- 
  TDINFACT-EXIT. 
 *---------------------------------------------------------------- 
      EXIT. 

Usage

See also

Related functions

Related documents