TDESCRIB

Description

Describes a column in a result row and the mainframe server program variable where it is stored.

Syntax

COPY SYGWCOB.
01 TDPROC                  PIC S9(9) USAGE COMP SYNC.
01 RETCODE                 PIC S9(9) USAGE COMP SYNC.
01 COLUMN-NUMBER           PIC S9(9) USAGE COMP SYNC.
01 HOST-VARIABLE-TYPE      PIC S9(9) USAGE COMP SYNC.
01 HOST-VARIABLE-MAXLEN    PIC S9(9) USAGE COMP SYNC.
01 HOST-VARIABLE-NAME      PIC X(n).
01 NULL-INDICATOR-VARIABLE PIC S9(4) USAGE COMP SYNC.
01 NULLS-ALLOWED           PIC S9(9) USAGE COMP SYNC.
01 COLUMN-TYPE             PIC S9(9) USAGE COMP SYNC.
01 COLUMN-MAXLEN           PIC S9(9) USAGE COMP SYNC.
01 COLUMN-NAME             PIC X(n).
01 COLUMN-NAME-LENGTH      PIC S9(9) USAGE COMP SYNC.
CALL 'TDESCRIB’ USING TDPROC, RETCODE, COLUMN-NUMBER, 
               HOST-VARIABLE-TYPE
               HOST-VARIABLE-MAXLEN,
               HOST-VARIABLE-NAME,
               NULL-INDICATOR-VARIABLE,
               NULLS-ALLOWED, COLUMN-TYPE, 
               COLUMN-MAXLEN, COLUMN-NAME,
                COLUMN-NAME-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-6.

COLUMN-NUMBER

(I) Number of the column that is being described. Columns are numbered sequentially. The first column in a row is number 1.

HOST-VARIABLE-TYPE

(I) Datatype of HOST-VARIABLE-NAME, the host program variable where the data for this column is stored. If you use TDCONVRT to convert from one datatype to another, this is the RESULT-TYPE.

HOST-VARIABLE-MAXLEN

(I) Maximum length of the host program variable. This is the value of (n) in the definition statement for HOST-VARIABLE-NAME.

For TDSVARYCHAR, TDSVARYBIN, and TDSVARYGRAPHIC variables, 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 actual length.

HOST-VARIABLE-NAME

(I) Host program variable that contains the data for this column.

You must name a different variable for each column to be described.

If you use TDCONVRT to convert from one datatype to another, this is the RESULT-VARIABLE. If the datatype is TDSVARYCHAR, TDSVARYBIN, or TDSVARYGRAPHIC, this is the name of a structure that includes the “LL” length specification.

NULL-INDICATOR-VARIABLE

(I) Host program variable that contains the NULL indicator for this column. When the value in this variable is negative, TDSNDROW sends a NULL value for this column. Note that this variable is a halfword.

If NULLS-ALLOWED is TDS-FALSE, this argument is ignored.

NULLS-ALLOWED – (I) Null permission indicator. Indicates whether NULLs are allowed for this column. Assign this argument one of the following values:

TDS-TRUE (1)

NULLs are allowed.

TDS-FALSE (0)

NULLs are not allowed.

NoteNULLs are typically used with DB2.

COLUMN-TYPE

(I) Open Client datatype of the column. This is the datatype used by the client application.

COLUMN-MAXLEN

(I) Maximum length of the column data. For variable-length datatypes, this argument represents the maximum length for a value of that datatype. For fixed-length datatypes (TDSINTn, TDSFLTn), this argument is ignored.

COLUMN-NAME

(I) Name of the column with the data that is being returned.

COLUMN-NAME-LENGTH

(I) Actual length of the column name.

Returns

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

Table 3-6: TDESCRIB return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

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-DUPLICATE-ENTRY (-9)

Duplicate column description. You attempted to describe the same column twice with a TDESCRIB statement. The operation failed.

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-DATA-TYPE (-171)

Illegal datatype. A sybase datatype supplied in the call is not supported and the conversion can not be completed.

TDS-INVALID-ID-VALUE (-10)

The specified column or parameter number is greater than the system maximum. Sybase allows as many columns per table result and parameters per RPC as the system maximum.

TDS-INVALID-LENGTH (-173)

Wrong length. The length specified in the COLUMN-MAXLEN argument is too short.

TDS-INVALID-NAMELENGTH (-179)

Invalid name length. The length specified for the column, parameter, message, or server name is invalid.

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

*	 Here we let TDESCRIB convert from DB2 varchar (TDSVARYCHAR)
*	 to DBCHAR.
 
	 CALL 'SYGETAD' USING DB-DESCRIBE-HV-PTR, EMPLOYEE-ED.
	 CALL 'SYGETAD' USING DB-COLUMN-NAME-HV-PTR, CN-ED.
	 MOVE LENGTH OF EMPLOYEE-ED TO WRKLEN1.
	 MOVE LENGTH OF CN-ED       TO WRKLEN2.
      MOVE TDSINT2               TO DB-HOST-TYPE.
      MOVE TDSINT2               TO DB-CLIENT-TYPE.
      PERFORM DESCRIBE-COLUMN.

 *    Get the user defined datatype of EMPLOYEE-ED column.
 
      CALL 'TDINFUDT' USING GWL-PROC, GWL-RC, CTR-COLUMN,
                            GWL-INFUDT-USER-TYPE.
 
 *    Set the user defined datatype of EMPLOYEE-ED column.
 
      CALL 'TDSETUDT' USING GWL-PROC, GWL-RC, CTR-COLUMN,
                            GWL-INFUDT-USER-TYPE.
 *-----------------------------------------------------------------
  DESCRIBE-COLUMN.
 *-----------------------------------------------------------------
      SET ADDRESS OF LK-DESCRIBE-HV    TO DB-DESCRIBE-HV-PTR.
      SET ADDRESS OF LK-COLUMN-NAME-HV TO DB-COLUMN-NAME-HV-PTR.
      ADD 1                            TO CTR-COLUMN.
 
      CALL 'TDESCRIB' USING GWL-PROC, GWL-RC, CTR-COLUMN,
                            DB-HOST-TYPE, WRKLEN1, LK-DESCRIBE-HV,
                            DB-NULL-INDICATOR, TDS-FALSE,
                            DB-CLIENT-TYPE, WRKLEN1,
	 LK-COLUMN-NAME-HV, WRKLEN2.

Usage


Datatype conversions

Table 3-7 shows which conversions are performed automatically when TDESCRIB is called.


For Japanese users

The Japanese Conversion Module (JCM) automatically converts column names from the character set used at the mainframe server to that specified by the client in the login packet.

See also

Related functions

Related topics