TDRCVSQL

Description

Receives a language string from a remote client.

Syntax

COPY SYGWCOB.
01 TDPROC               PIC S9(9)  USAGE COMP SYNC.
01 RETCODE              PIC S9(9)  USAGE COMP SYNC.
01 HOST-VARIABLE        PIC X(n).
01 MAX-VAR-LENGTH       PIC S9(9)  USAGE COMP SYNC.
01 ACTUAL-STRING-LENGTH PIC S9(9)  USAGE COMP SYNC.
CALL 'TDRCVSQL' USING TDPROC, RETCODE,HOST-VARIABLE, 
                  MAX-VAR-LENGTH,ACTUAL-STRING-LENGTH.

Parameters

TDPROC

(I) Handle for this client/server connection. This must be the same value specified in the associated TDACCEPT call. 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-26.

HOST-VARIABLE

(O) Host program variable where the text of the retrieved language string is stored.

MAX-VAR-LENGTH

(I) Maximum length of the string that can be stored in the named HOST-VARIABLE. For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes.

ACTUAL-STRING-LENGTH

(O) The actual length of the incoming data, in bytes. If this length is greater than the specified MAX-VAR-LENGTH, the data is truncated.

NoteIf this is a Japanese character set, the length may be halved when converted to IBM Kanji by Gateway-Library.

Returns

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

Table 3-26: TDRCVSQL return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CANCEL-RECEIVED (-12)

Operation canceled. The remote partner issued a cancel. The current operation failed.

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-CONNECTION-TERMINATED (-4997)

Connection closed. The remote partner closed (deallocated) the client/server connection.

TDS-ILLEGAL-REQUEST (-5)

Illegal function. The operation failed. This code can indicate that a client application is trying to use a Gateway-Library function that is not supported for clients (for example, TDSNDROW).

TDS-INVALID-LENGTH (-173)

Wrong length. The length specified in the MAX-VAR-LENGTH argument is too short. The length must be greater than zero.

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-NO-SQL-PRESENT (101)

No incoming language string present. TDRCVSQL cannot retrieve more text because no more text was accepted. The operation failed.

TDS-TRUNCATION-OCCURRED (-13)

Data was truncated. The actual data length was longer than the maximum data length allotted for this data.

TDS-WRONG-STATE (-6)

This function cannot be used in the current communication state. For example, your program tried to send a reply before it read in all of the client parameters. The application was still in RECEIVE state and could not send. The operation failed.

Examples

Example 1

The following code fragment illustrates the use of TDSQLLEN and TDRCVSQL to receive a language request from the client. 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.
       *    Ensure kicked off via language request
       *    (this could be handled more reasonably by TDRESULT)
 
            CALL 'TDINFPGM' USING GWL-PROC, GWL-RC,
                                  GWL-INFPGM-TDS-VERSION,
                                  GWL-INFPGM-LONGVAR,
                                  GWL-INFPGM-ROW-LIMIT,
                                  GWL-INFPGM-REMOTE-TRACE,
                                  GWL-INFPGM-CORRELATOR,
                                  GWL-INFPGM-DB2GW-OPTION,
                                  GWL-INFPGM-DB2GW-PID,
                                  GWL-INFPGM-TYPE-RPC.
            IF GWL-INFPGM-TYPE-RPC NOT = TDS-START-SQL
                MOVE MSG-NOT-LANG           TO MSG-TEXT
                MOVE LENGTH OF MSG-NOT-LANG TO MSG-TEXT-L
                PERFORM SEND-ERROR-MESSAGE
                GO TO END-PROGRAM
            END-IF.
 
       *    Prepare for receive
 
            CALL 'TDRESULT' USING GWL-PROC, GWL-RC.
 
       *    Get lenth of language text, ensure not too big for us
       *    (this could be handled without TDSQLLEN by checking
       *    LANG-ACTUAL-LEN doesn't exceed LANG-MAX-L in TDRCVSQL call)
 
            CALL 'TDSQLLEN' USING GWL-PROC, GWL-SQLLEN.
            MOVE LENGTH OF LANG-BUFFER-TEXT TO LANG-MAX-L.
 
            IF GWL-SQLLEN > LANG-MAX-L THEN
                MOVE MSG-BAD-LEN           TO MSG-TEXT
                MOVE LENGTH OF MSG-BAD-LEN TO MSG-TEXT-L
                PERFORM SEND-ERROR-MESSAGE
                GO TO END-PROGRAM
            END-IF.
       *    Get language text
            CALL 'TDRCVSQL' USING GWL-PROC, GWL-RC,
                                  LANG-BUFFER-TEXT,
                                  LANG-MAX-L,
                                  LANG-ACTUAL-L.
            MOVE LANG-ACTUAL-L TO LANG-BUFFER-LL.

Usage


For Japanese users

See also

Related functions