CTBDESCRIBE

Description

Returns a description of result data.

Syntax

COPY CTPUBLIC.
01 COMMAND        PIC S9(9) COMP SYNC.
01 RETCODE        PIC S9(9) COMP SYNC.
01 ITEM-NUM       PIC S9(9) COMP SYNC.
01 DATAFMT
05 FMT-NAME       PIC X(132).
05 FMT-NAMELEN    PIC S9(9) COMP SYNC.
05 FMT-TYPE       PIC S9(9) COMP SYNC.
05 FMT-FORMAT     PIC S9(9) COMP SYNC.
05 FMT-MAXLEN     PIC S9(9) COMP SYNC.
05 FMT-SCALE      PIC S9(9) COMP SYNC.
05 FMT-PRECIS     PIC S9(9) COMP SYNC.
05 FMT-STATUS     PIC S9(9) COMP SYNC.
05 FMT-COUNT      PIC S9(9) COMP SYNC.
05 FMT-UTYPE      PIC S9(9) COMP SYNC. 
05 FMT-LOCALE     PIC S9(9) COMP SYNC.
CALL 'CTBDESCR' USING COMMAND RETCODE ITEM-NUM DATAFMT.

Parameters

COMMAND

(I) Handle for this client/server operation. This handle is defined in the associated CTBCMDALLOC call.

RETCODE

(O) Variable where the result from an executed function returns. Its value is one of the codes listed under “Return value,” in this section.

ITEM-NUM

(I) Ordinal number of the column, parameter, or status being returned. This value is an integer.

When describing a column, ITEM-NUM is the column number. For example, the first column in the select list of a SQL select statement is column number 1, the second is column number 2, and so forth.

When describing a return parameter, ITEM-NUM is the ordinal rank of the parameter. The first parameter returned by a procedure or transaction is number 1. Adaptive Server stored procedure return parameters are returned in the order originally specified in the stored procedure’s create procedure statement. This is not necessarily the same order as specified in the RPC that invoked the stored procedure or transaction.

In determining what number to assign to ITEM-NUM, do not count non-return parameters. For example, if the second parameter in a stored procedure or transaction is the only return parameter, its ITEM-NUM is 1.

When describing a stored procedure return status, ITEM-NUM must be 1, because there can be only a single status in a return status result set.

To clear all bindings, assign ITEM-NUM a value of CS-UNUSED.

DATAFMT

(O) A structure that contains a description of the result data item referenced by ITEM-NUM. This structure is also used by CTBBIND, CTBPARAM and CSBCONVERT and is explained in the Topics chapter, under “DATAFMT structure”.

WARNING! You must initialize DATAFMT to zeroes. Failure to do so causes addressing exceptions.

The DATAFMT structure contains the following fields listed in Table 3-9.

Table 3-9: Fields in the DATAFMT structure for CTBDESCRIBE

When this field

Is used with these result items

CTBDESCRIBE sets the field to

FMT-NAME

Regular columns, return parameters

The null-terminated name of the data item, if any. To indicate that there is no name, set FMT-NAMELEN to 0.

FMT-NAMELEN

Regular columns, return parameters

The actual length, in bytes, of FMT-NAME, not including the null terminator.

A zero value here indicates no name.

FMT-TYPE

Regular columns, return parameters, return status

The datatype of the data item. All “Datatypes” are valid.

A return status always has a datatype of CS-INT.

FMT-FORMAT

Not used (CS-FMT-UNUSED)

Not applicable.

FMT-MAXLEN

Regular columns, return parameters

The maximum possible length, in bytes, of the data for the column or parameter being described.

FMT-SCALE

Regular columns and return parameters for which the datatype is packed decimal (CS-PACKED370), or Sybase-decimal/numeric

The number of digits to the right of the decimal point.

FMT-PRECIS

Regular columns and return parameters for which the datatype is packed decimal (CS-PACKED370), or Sybase-decimal/numeric

The total number of decimal digits in the result data item.

FMT-STATUS

Regular columns only

One or more of the following symbolic values, added together:

  • CS-CANBENULL to indicate a column that was tagged “nullable” by the server.

  • CS-NODATA to indicate that no data is associated with the column.

FMT-COUNT

Regular columns, return parameters, return status

The number of rows copied to destination variables per CTBFETCH call. CTBDESCRIBE initializes FMT-COUNT as 1 to provide a default value in case an application uses the CTBDESCRIBE return DATAFMT structure as the CTBBIND input DATAFMT structure.

This value is always 1 for return parameters and status results.

FMT-UTYPE

Regular columns, return parameters

The user-defined datatype of the column or parameter, if any. FMT-UTYPE is set in addition to (not instead of) DATATYPE.

Note This field is used for datatypes defined at the server, not for Open Client user-defined datatypes.

FMT-LOCALE

Reserved for future use

Not applicable.

Returns

CTBDESCRIBE returns one of the following values listed in Table 3-10.

Table 3-10: CTBDESCRIBE return values

Value

Meaning

CS-SUCCEED (-1)

The routine completed successfully.

CS-FAIL (-2)

The routine failed.

CTBDESCRIBE returns CS-FAIL if ITEM-NUM does not represent a valid result data item.

TDS-CANCEL-RECEIVED (-12)

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

TDS-CONNECTION-TERMINATED (-4997)

The connection is not active.

TDS-NO-COMPUTES-ALLOWED (-60)

Compute results are not supported.

TDS-RESULTS-CANCELED (-49)

A cancel was sent to purge results.

TDS-WRONG-STATE (-6)

Program is in the wrong communication state to issue this call.

Examples

Example 1

The following code fragment demonstrates the use of CTBDESCRIBE. It is taken from the sample program SYCTSAA5 in Appendix A, “Sample Language Requests.”

      	 *========================================================
       *==                                                    ==
       *== Subroutine to process result rows                  ==
       *==                                                    ==
       *========================================================
        RESULT-ROW-PROCESSING.
  
            CALL 'CTBRESIN' USING CSL-CMD-HANDLE,
                                  CSL-RC,
                                  CS-NUMDATA,
                                  RF-NUMDATA,
                                  RF-NUMDATA-SIZE,
                                  CF-COL-LEN.
  
            IF CSL-RC NOT EQUAL CS-SUCCEED
              THEN
                MOVE SPACES TO MSGSTR
                STRING 'CTBRESINFO failed' DELIMITED BY SIZE
                                                       INTO MSGSTR
                PERFORM PRINT-MSG
                PERFORM ALL-DONE
            END-IF.
  
            COMPUTE FF-ROW-NUM = FF-ROW-NUM + 1.
  
       *********************************
       * display number of connections *
       *********************************
  
            MOVE CF-MAXCONNECT   TO OR2-MAXCONNECT.
            MOVE OUTPUT-ROW-STR2 TO RSLTNO(FF-ROW-NUM).
            COMPUTE FF-ROW-NUM = FF-ROW-NUM + 2.
  
       *********************************
       * display the number of columns *
       *********************************
  
            MOVE RF-NUMDATA      TO OR4-NUMDATA.
            MOVE OUTPUT-ROW-STR4 TO RSLTNO(FF-ROW-NUM).
  
            IF RF-NUMDATA NOT EQUAL 2
              THEN
                STRING 'CTBRESINFO returned wrong # of parms' DELIMITED
                                               BY SIZE INTO MSGSTR
                PERFORM PRINT-MSG
                PERFORM ALL-DONE
            END-IF.
  
            COMPUTE FF-ROW-NUM = FF-ROW-NUM + 2.
  
       **------------------------------------------------------------
       **   Setup column headings
       **------------------------------------------------------------
  
            MOVE 'FirstName    EducLvl' TO RSLTNO(FF-ROW-NUM).
            COMPUTE FF-ROW-NUM = FF-ROW-NUM + 1.
            MOVE '===========  =======' TO RSLTNO(FF-ROW-NUM).
  
            PERFORM BIND-COLUMNS
               VARYING I FROM 1 BY 1
                  UNTIL I IS GREATER THAN RF-NUMDATA.
  
        RESULT-ROW-PROCESSING-EXIT.
            EXIT.
  
       *========================================================
       *==                                                    ==
       *== Subroutine to bind each data                       ==
       *==                                                    ==
       *========================================================
        BIND-COLUMNS.
  
             CALL 'CTBDESCR' USING CSL-CMD-HANDLE,
                                   CSL-RC,
                                   I,
                                   DATAFMT.
  
             IF CSL-RC NOT EQUAL CS-SUCCEED
               THEN
                 MOVE SPACES TO MSGSTR
                 STRING 'CTBDESCR failed'
                        DELIMITED BY SIZE INTO MSGSTR
                 PERFORM PRINT-MSG
                 PERFORM ALL-DONE
             END-IF.
  
       **--------------------------------------------------------
       **   We need TO bind the data TO program variables.
       **   We don't care about the indicaTOr variable
       **   so we'll pass NULL for that PARAMeter in OC-BIND().
       **--------------------------------------------------------
  
       ******************
       * ROWs per FETCH *
       ******************
              MOVE 1 TO DF-COUNT
  
              EVALUATE DF-DATATYPE
  
                WHEN CS-SMALLINT-TYPE
  
                  CALL 'CTBBIND' USING CSL-CMD-HANDLE,
                                       CSL-RC,
                                       I,
                                       DATAFMT,
                                       DATA-SMALLINT,
                                       CF-COL-LEN,
                                       CS-PARAM-NOTNULL,
                                       CF-COL-INDICATOR,
                                       CS-PARAM-NULL
  
                  IF CSL-RC NOT EQUAL CS-SUCCEED
                    THEN
                      MOVE SPACES TO MSGSTR
                      STRING 'CTBBIND CS-SMALLINT-TYPE failed' DELIMITED
                                               BY SIZE INTO MSGSTR
                      PERFORM PRINT-MSG
                      PERFORM ALL-DONE
                  END-IF
  
                WHEN CS-VARCHAR-TYPE
  
                  MOVE LENGTH OF CF-COL-FIRSTNME-TXT TO DF-MAXLENGTH
  
                  CALL 'CTBBIND' USING CSL-CMD-HANDLE,
                                       CSL-RC,
                                       I,
                                       DATAFMT,
                                       CF-COL-FIRSTNME,
                                       CF-COL-LEN,
                                       CS-PARAM-NOTNULL,
                                       CF-COL-INDICATOR,
                                       CS-PARAM-NULL
  
                  IF CSL-RC NOT EQUAL CS-SUCCEED
                    THEN
                      MOVE SPACES TO MSGSTR
                      STRING 'CTBBIND CS-VARCHAR-TYPE failed' DELIMITED
                                               BY SIZE INTO MSGSTR
                      PERFORM PRINT-MSG
                      PERFORM ALL-DONE
                  END-IF.
  
        BIND-COLUMNS-EXIT.
            EXIT.

Usage

See also

Related functions

Related topics