TDSETPRM

Description

Specifies the content and length of a return parameter before returning it to a remote client.

Syntax

COPY SYGWCOB.
01 TDPROC               PIC S9(9)  USAGE COMP SYNC.
01 RETCODE              PIC S9(9)  USAGE COMP SYNC.
01 PARM-ID              PIC S9(9)  USAGE COMP SYNC.
01 HOST-VARIABLE-TYPE   PIC S9(9)  USAGE COMP SYNC.
01 HOST-VARIABLE-LENGTH PIC S9(9)  USAGE COMP SYNC.
01 HOST-VARIABLE        PIC X(n).
01 USER-DATATYPE        PIC S9(9)  USAGE COMP SYNC.
CALL 'TDSETPRM' USING TDPROC, RETCODE, PARM-ID, 
               HOST-VARIABLE-TYPE, 
               HOST-VARIABLE-LENGTH, HOST-VARIABLE,
                 USER-DATATYPE.

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

PARM-ID

(I) Number of the parameter to be returned. This must be the same parameter ID specified in the TDRCVPRM call that retrieved this parameter. Parameters are numbered sequentially in the order received, from 1 to 255.

HOST-VARIABLE-TYPE

(I) Datatype of the HOST-VARIABLE.

HOST-VARIABLE-LENGTH

(I) Length of the HOST-VARIABLE.

If HOST-VARIABLE-TYPE is TDSVARYCHAR, TDSVARYBIN, or TDSVARYGRAPHIC, this length does not include the 2 bytes for the “LL” length specification. For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes (actual length).

HOST-VARIABLE

(I) Name of the host program variable that contains the return data.

USER-DATATYPE

(I) The client-specified datatype of the parameter, if any. If no user datatype is specified, code 0 for this field. Currently, this argument is ignored.

Returns

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

Table 3-32: TDSETPRM return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CONNECTION-TERMINATED (-4997)

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

TDS-DATE-CONVERSION-ERROR (-23)

Error in conversion of datetime data. This can be a result of trying to convert short datetime (TDSDATETIME4) for a client using an early TDS version. TDS versions earlier than 4.2 do not support the short datetime datatype.

TDS-DECIMAL-CONVERSION-ERROR (-24)

Error in conversion of packed decimal data.

TDS-ENTRY-NOT-FOUND (-8)

The specified column number, transaction number, or parameter does not exist.

TDS-FLOAT-CONVERSION-ERROR (-21)

Error in conversion of float values.

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-DATA-CONVERSION (-172)

Incompatible datatypes. The source datatype cannot be converted into the requested result datatype.

TDS-INVALID-LENGTH (-173)

Wrong length. The length specified in the HOST-VARIABLE-LENGTH argument is too long.

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-INVALID-VAR-ADDRESS (-175)

Specified variable address is invalid. No variable with the specified name exists. A NULL value was specified. The operation failed.

TDS-MONEY-CONVERSION-ERROR (-22)

Error in conversion of TDSMONEY-type data. This can be a result of trying to convert to short money (TDSMONEY4) for a client using an early TDS version. TDS versions earlier than 4.2 do not support the short money datatype.

TDS-TRUNCATION-ERROR (-20)

Error occurred in truncation of data value.

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 a typical use of TDSETPRM. This example is taken from the sample program, SYCCSAR2, in Appendix B, “Sample RPC Application for CICS.”

 	 PERFORM DESCRIBE-COLUMN.
	 PERFORM FETCH-AND-SEND-ROWS UNTIL ALL-DONE 
*     Update returned parameter with number of rows fetched
      CALL 'TDSETPRM' USING   GWL-PROC, GWL-RC, GWL-SETPRM-ID,
                               GWL-SETPRM-TYPE, GWL-SETPRM-DATA-L,
                               PARM-RETURN-ROWS,
                                GWL-SETPRM-USER-DATA.
      GO TO END-PROGRAM.

Usage


Datatype conversions

When sending data to a client, TDSETPRM converts many datatypes from the Gateway-Library (source) datatype to the client (result) datatype. Table 3-33 shows what conversions are possible.

Table 3-33: Datatype conversions performed by TDSETPRM

Source datatype: Gateway-Library

Result datatype: Open Client

Notes

TDSCHAR TDSCHAR TDSVARYCHAR TDSVARYCHAR TDSLONGVARCHAR TDSLONGVARCHAR TDSMONEY TDSMONEY

TDSVARYCHAR TDSLONGVARCHAR TDSCHAR TDSLONGVARCHAR TDSCHAR TDSVARYCHAR TDSCHAR TDSVARYCHAR

Does EBCDIC to ASCII conversion. For Japanese characters, converts to workstation datatype. Pads TDSCHAR fields with blanks.

TDSFLT8 TDSFLT8 TDSFLT8 TDSFLT4 TDSFLT4 TDSFLT4

TDSFLT4 TDSMONEY TDSMONEY4 TDSFLT8 TDSMONEY TDSMONEY4

Truncates low order digits.

TDSCHAR TDSVARYCHAR

TDSMONEY TDSMONEY

TDS-PACKED-DECIMAL TDS-PACKED-DECIMAL TDS-PACKED-DECIMAL TDS-PACKED- DECIMAL

TDSCHAR TDSVARYCHAR TDSFLT8 TDSMONEY

When converting packed decimal to character values, change the length to allow for unpacking, leading or trailing zeros, the sign and the decimal point.

TDSGRAPHIC TDSGRAPHIC TDSVARYGRAPHIC TDSVARYGRAPHIC

TDSCHAR TDSVARYCHAR TDSCHAR TDSVARYCHAR

Used with Japanese double-byte character sets. Pads TDSCHAR fields with blanks.

TDSDATETIME TDSDATETIME4

TDSCHAR TDSCHAR

TDSCHAR TDSCHAR

TDSNUMERIC TDS-SYBASE-DECIMAL

Use TDSETBCD to set Sybase numeric or decimal precision and scale before TDSETPRM.

TDS-PACKED-DECIMAL TDS-PACKED-DECIMAL

TDSNUMERIC TDS-SYBASE-DECIMAL

Use TDSETBCD to set Sybase numeric or decimal precision and scale before TDSETPRM.

See also

Related functions