TDSETPT

Description

Specifies the type of IMS TM transaction being used.

NoteThis function is for use with IMS TM programs only. CICS programs ignore this call. MVS programs do not ignore this call.

Syntax

COPY SYGWCOB.
01 IHANDLE   PIC S9(9)  USAGE COMP SYNC.
01 RETCODE   PIC S9(9)  USAGE COMP SYNC.
01 PROG-TYPE PIC X(4).
01 SPA       PIC X(n).
01 RESERVED1 PIC S9(9)  USAGE COMP SYNC.
01 RESERVED1 PIC S9(9)  USAGE COMP SYNC.
CALL 'TDSETPT' USING IHANDLE, RETCODE, PROG-TYPE, 
                SPA, RESERVED1, RESERVED2.

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

PROG-TYPE

(I) Type of IMS TM program being called. This is a 4-byte padded field.

Assign this argument one of the following IMS TM program types:

MPP

An IMS TM online (implicit or Adapter) message processing program that runs in an IMS TM message processing region. This is the default.

BMP

An IMS TM batch message program that runs in an IMS TM batch message processing region.

CONV

An IMS TM message processing program that uses the IMS TM scratch pad area (SPA).

EXPL

An IMS TM message processing program that uses the explicit API. This is the only option that supports long-running transactions.

Under CICS: If you leave this field blank, Gateway-Library ignores this value and assumes a standard CICS program.

Under IMS TM: If you leave this field blank, Gateway-Library assumes a standard IMS TM MPP program.

Under MVS: PROG-TYPE must be EXPL.

SPA

(I) The IMS TM scratch pad area where conversational transaction results are stored.

When PROG-TYPE is CONV, this argument is required. For other program types, set this field to zeroes, and Gateway-Library ignores this field.

RESERVED1

(I) Reserved for future use.

RESERVED2

(I) Reserved for future use.

Returns

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

Table 3-34: TDSETPT 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 TDINIT, TDSETPT, and TDACCEPT at the beginning of a Gateway-Library program that uses the IMS TM implicit API. This example is taken from the sample program in Appendix D, “Sample RPC Application for IMS TM (Implicit).”

*    establish gateway environment
     CALL ‘TDINIT’ USING IO-PCB, GWL-RC, GWL-INIT-HANDLE. 
            . [check return code]
      .
 *    set program type to MPP 
     CALL ‘TDSETPT’ USING GWL-INIT-HANDLE, GWL-RC, 
                           GWL-PROG-TYPE, GWL-SPA-PTR, 
                           TDS-NULL, TDS- NULL.
            . [check return code]
      .
*    accept client request
     CALL ‘TDACCEPT’ USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE, 
                              SNA-CONNECTION-NAME, 
                              SNA-SUBC. 
*----------------------------------------------------------------
 READ-IN-USER-PARM. 
*----------------------------------------------------------------

Usage

NoteIf your transaction is conversational (CONV), you must insert the scratch pad area into the IO/PCB before sending the results with TDSNDROW.

See also

Related functions

Related topics