TDACCEPT

Description

Accepts a request from a remote client. This function returns the handle for the SNA or TCP/IP conversation in the TDPROC program variable.

Syntax

COPY SYGWCOB.
01 TDPROC 		 	PIC S9(9) USAGE COMP SYNC.
01 RETCODE 		 	PIC S9(9  USAGE COMP SYNC.
01 IHANDLE 			PIC S9(9) USAGE COMP SYNC.
01 ACCEPT-CONNECTION-NAME 								PIC X(8)  VALUE IS SPACES.
01 ERROR-SUBCODE          								PIC S9(9) USAGE COMP SYNC.
CALL 'TDACCEPT’ USING TDPROC, RETCODE, IHANDLE,  ACCEPT-CONNECTION-NAME, ERROR-SUBCODE.

Parameters

TDPROC

(O) Handle for this client/server connection. All subsequent server functions using this connection must specify this same value in their TDPROC argument. The TDPROC handle corresponds to the connection and command handles 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-2.

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.

ACCEPT-CONNECTION-NAME

(I) Leave blank. CICS and IMS TM get this information elsewhere.

ERROR-SUBCODE

(O) Detailed error information. Provides additional information about the cause of failure when TDACCEPT returns a return code other than TDS-OK. For a list of error subcodes, see Mainframe Connect Client Option and Server Option Messages and Codes.

Returns

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

Table 3-2: TDACCEPT return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CHARSET-NOTLOADED (-261)

Gateway-Library found the DBCS specified by the client, but the corresponding double-byte module was not loaded at the mainframe.

This code is retuned to TDACCEPT when a client specifies a DBCS (for example, Shift-JIS) for which the associated translate module was not loaded or defined to the mainframe system.

If the TP system is CICS, this can mean that the translate module was not defined in RDO (or to the PPT table), or that it is not present in the LOADLIB.

TDS-CHARSETSRV-NOT-SBCS (-264)

The client character set was not found; DBCS specified as default.

This code represents two problems:

  1. The character set named in the client login packet was not found in the table of character set names. This may indicate that the client did not specify the character set correctly (for example, the -J option in isql or the DBSETLCHARSET value in a DB-Library program is invalid).

  2. Open ServerConnect was customized to process single-byte character sets, but the default character set is double-byte. This usually indicates that the customization settings are incorrect for kanji support.

TDS-CONNECTION-FAILED (-4998)

Connection abended. The client/server connection abnormally ended (for example, the LU 6.2 session crashed or the remote transaction abended).

TDS-DBCS-CHARSET-NOTFOUND (-263)

Gateway-Library could not find the DBCS specified in the client login packet.

This usually indicates that the client request specified an invalid character set in, for example, the -J option in isql or the DBSETLCHARSET value in a DB-Library program.

TDS-DEFAULT-CHARSET-NOTFOUND (-262)

The client login packet did not specify a character set or the specified client character set could not be found, and Gateway-Library did not find the default. This code is returned for single-byte character sets only.

TDS-GWLIB-UNAVAILABLE (-15)

Could not load SYGWCICS (the Gateway-Library phase).

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-INVALID-TDPROC (-18)

Error in specifying a value for the TDPROC argument.

TDS-SOS (-257)

Memory shortage. The host subsystem was unable to allocate enough memory for the control block that Gateway-Library was trying to create. The operation failed.

TDS-USING-DEFAULT-CHARSETSRV (10)

Gateway-Library using default character set.

The client login packet did not specify a character set, or Gateway-Library could not find the specified single-byte character set, so it used the default character set specified during customization. This is an informational message.

Examples

Example 1

The following code fragment illustrates the use of TDINIT, TDACCEPT, TDRESULT, TDSNDDON, and TDFREE at the beginning and end of a Gateway-Library program. This example is taken from the sample program, SYCCSAR2, in Appendix B, “Sample RPC Application for CICS.”

*    Establish gateway environment

CALL 'TDINIT' USING DFHEIBLK, GWL-RC, GWL-INIT-HANDLE.

*    Accept client request

CALL 'TDACCEPT' USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,SNA-CONNECTION-NAME, SNA-SUBC.

*    TDRESULT to make sure we were started via RPC request

CALL 'TDRESULT' USING GWL-PROC, GWL-RC.
	IF GWL-RC NOT = TDS-PARM-PRESENT 
	THEN PERFORM TDRESULT-ERROR
	GO TO END-PROGRAM
	END-IF.

* -------------------------------------------------------------
* body of program
* -------------------------------------------------------------
*-----------------------------------------------------------------
END-PROGRAM.
*-----------------------------------------------------------------
     IF SEND-DONE-OK
          MOVE TDS-DONE-COUNT TO WRK-DONE-STATUS
      ELSE
          MOVE TDS-DONE-ERROR TO WRK-DONE-STATUS
          MOVE ZERO           TO PARM-RETURN-ROWS
      END-IF.
	 CALL 'TDSNDDON' USING GWL-PROC, GWL-RC, WRK-DONE-STATUS,
                            PARM-RETURN-ROWS, TDS-ZERO,
                            TDS-ENDRPC.
	CALL 'TDFREE' USING GWL-PROC, GWL-RC.
	EXEC CICS RETURN END-EXEC.

Example 2

The following code fragment illustrates the use of TDINIT, TDSETPT, and TDACCEPT at the beginning of a Gateway-Library program that uses the IMS 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


Character set translations

After Gateway-Library accepts the client request, it converts the request into a form understood by the mainframe. Roman characters are converted from ASCII to EBCDIC. Japanese characters are converted to IBM-Kanji.

Gateway-Library uses translate tables to do these conversions. Single-byte translate tables can be customized locally. The Japanese Conversion Module has its own set of conversion tables.

The Open ServerConnect environment is customized at the customer site. During customization, you define the type of requests that Gateway-Library will process. Customized items related to international applications include:

When TDACCEPT retrieves the client character set from the login packet, it looks up that character set in a table of supported character set names. If it finds a match in that table, it uses the associated translate table or conversion module to convert the request to mainframe characters.

If no character set is specified in the login packet, or if Gateway-Library cannot find a match for the specified client character set, the action taken by TDACCEPT depends on whether or not a double-byte character set was specified during customization.

When the character set is single-byte:

When the character set is double-byte:


For Japanese users

Japanese requests are processed by the Japanese Conversion Module (JCM), a separate tape that provides Japanese language support for Open ServerConnect. The JCM must be installed and defined to your mainframe system before Gateway-Library can process client requests written in Japanese.

Within a Gateway-Library program, TDINIT loads the JCM. If it cannot load that module, TDINIT does not return an error code. However, when a client request specifies a double-byte character set in the login packet, TDACCEPT returns TDS-CHARSET-NOTLOADED.

If your program uses the JCM, TDACCEPT converts the name of each parameter to the character set used at the mainframe.

See also

Related functions

Related topics

Related documents