CTBBIND

Description

Associates a returned column, parameter, or status with a program variable.

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.
01 BUFFER 
01 COPIED           PIC S9(9) COMP SYNC.
01 COPIED-NULL      PIC S9(9) COMP SYNC.
01 INDICATOR        PIC S9(4) COMP SYNC.
01 INDICATOR-NULL   PIC S9(9) COMP SYNC.
CALL 'CTBBIND' USING COMMAND RETCODE ITEM-NUM DATAFMT 
BUFFER COPIED-NULL INDICATOR-NULL.

Parameters

COMMAND

(I) Handle for this connection. This is the handle defined in the CTBCMDALLOC call for this connection. The command handle corresponds to the TDPROC handle in the Open ServerConnect Gateway-Library.

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 result column, return parameter, or return status value that is to be bound.

When binding a result 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 binding a return parameter:

  • ITEM-NUM is the ordinal rank of the return parameter. The first parameter returned by a procedure or parameter is number 1. Adaptive Server stored procedure return parameters are returned in the order originally specified in the create procedure statement for the stored procedure. 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 is the only return parameter, its ITEM-NUM is 1.

When binding a stored procedure return status:

  • ITEM-NUM must be 1. There is only one column and one row in a return status result set.

To clear all bindings:

  • Assign ITEM-NUM a value of CS-UNUSED.

DATAFMT

(I) A structure that contains a description of the destination variable(s). This structure is also used by CTBDESCRIBE, CTBPARAM and CSBCONVERT and is explained in Chapter 2, “Topics”, under “DATAFMT structure”.

Table 3-2 lists the fields in the DATAFMT structure, indicates whether they are used by CTBBIND, and contains general information about each field. CTBBIND ignores DATAFMT fields that it does not use.

WARNING! You must initialize the entire DATAFMT structure to zeroes or low values. Failure to do so causes addressing exceptions.

Table 3-2: Fields in the DATAFMT structure for CTBBIND

Field

When used

Value represents

FMT-NAME

Not used (CS-FMT-UNUSED).

Not applicable.

FMT-NAMELEN

Not used (CS-FMT-UNUSED).

Not applicable.

FMT-TYPE

When binding all types of results.

The datatype of the destination variable (BUFFER). All datatypes listed under “Datatypes” are valid.

CTBBIND supports a wide range of datatype conversions, so FMT-TYPE can be different from the datatype returned by the server. For instance, by specifying a datatype of CS-FLOAT, you can bind a CS-MONEY or CS-MONEY4 value to a float-type program variable. The appropriate data conversion happens automatically.

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

FMT-FORMAT

When binding results to fixed-length character or binary destination variables.

In all other cases, this field is unused (CS-FMT-UNUSED).

The destination format of character or binary data.

For fixed-length character-type destinations only:

CS-FMT-PADBLANK—pads to the full length of the variable with blanks.

For fixed-length character or binary type destination variables:

CS-FMT-PADNULL—pads to the full length of the variable with LOW-VALUES.

FMT-MAXLEN

When binding all types of results to non-fixed-length types.

FMT-MAXLEN is ignored when binding to fixed-length datatypes.

The length of the destination variable, in bytes. If BUFFER has more than one element (that is, it is an array), FMT-MAXLEN is the length of one element.

When binding to character or binary destinations, FMT-MAXLEN must describe the total length of the destination variable, including any space required for special terminating bytes, with this exception: when binding to a VARYCHAR-type destination such as DB2’s VARCHAR, FMT-MAXLEN does not include the length of the “LL” length specification.

To clear bind values, assign FMT-MAXLEN a value of 0.

If the length specified in FMT-MAXLEN is too small to hold a result data item, then, at fetch time, CTBFETCH will discard the result item that is too large, fetch any remaining items in the row, and return CS-ROW-FAIL. If this occurs, the contents of BUFFER will be undefined.

When binding Sybase-numerical/decimal to char, use CTDESCRIBE to determine precision. FMT-MAXLEN should be precision + 2 in this case. When binding to packed decimal CTBBIND calculates FMT-MAXLEN as (precision/2) + 1.

FMT-SCALE

Only when converting column results or return parameters to or from an Open ServerConnect packed decimal (CS-PACKED370), Sybase-decimal, and Sybase-numeric datatypes.

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

If the source value is the same datatype as the destination value, set FMT-SCALE to CS-SRC-VALUE to indicate that the destination variable should pick up the value for FMT-SCALE from the source data.

FMT-SCALE must be less than or equal to FMT-PRECIS and cannot be greater than 31. If the actual scale is greater than the scale specified in FMT-SCALE but not greater than 31, CTBBIND truncates the results and issues a warning. If the actual scale is greater than 31, the CTBBIND call fails.

When binding sybase-numeric/decimal to char or packed-decimal use CTDESCRIBE to determine precision and scale.

FMT-PRECIS

Only when converting column results or return parameters to an Open ServerConnect packed decimal (CS-PACKED370), Sybase-decimal, and Sybase-numeric datatypes.

The total number of decimal digits in the destination variable. This is the n in the BUFFER declaration: PIC S9(n)VG(m).

If the source data is the same datatype as the destination variable, setting FMT-PRECIS to CS-SRC-VALUE instructs the destination variable to pick up its value for FMT-PRECIS from the source data.

If the precision of the value fetched exceeds the precision of the destination variable, CTBFETCH returns a warning message.

FMT-PRECIS must be greater than or equal to FMT-SCALE and cannot be less than 1 or greater than 31.

FMT-STATUS

Not used.

Not applicable.

FMT-COUNT

When binding all types of results.

Only regular row result sets ever contain multiple rows. Other types of results (for example, return parameters, status) are treated like a single row of results.

The number of result rows to be copied to program variables per CTBFETCH call. If FMT-COUNT is larger than the number of available rows, only the available rows are copied.

FMT-COUNT must have the same value for all columns in a result set according to the following:

  • If FMT-COUNT is 0 or 1, 1 row is fetched

  • If FMT-COUNT is greater than 1, it represents the number of rows that are fetched. In this case, BUFFER must be an array.

NoteOnly regular row result sets can contain multiple rows. Other types of results (such as return parameters and status) are treated like a single row of results.

FMT-UTYPE

Not used.

Not applicable.

FMT-LOCALE

Not used.

Reserved for future use.

BUFFER

(I) Destination variable. A single field or an array of n elements where n is FMT-COUNT. Each array element is of size FMT-MAXLEN.

BUFFER is the program variable to which CTBBIND binds the server results. When the application calls CTBFETCH to fetch the result data, it is copied into this space.

The definition of the argument depends on the datatype of the destination variable. See Table 3-4 for a list of possible values.

If you no longer want to store incoming data in this buffer, set FMT-MAXLEN to 0. This clears the binding.

COPIED

(O) Length of the incoming data. This can be a single field or, if BUFFER is an array, it can be an array of n elements where n is FMT-COUNT. At fetch time, CTBFETCH fills COPIED with the length(s) of the copied data.

COPIED-NULL

(I) NULL indicator for COPIED. This argument allows you to indicate that COPIED should be treated as null (LOW-VALUES). Assign this argument one of the following values:

Value

Meaning

CS-PARAM-NULL (-102)

COPIED is LOW-VALUES.

If COPIED is an array, assigning CS-PARAM-NULL to this argument causes all elements of COPIED to be treated as LOW-VALUES.

CS-PARAM-NOTNULL (-103)

COPIED is not LOW-VALUES.

INDICATOR

-(O) From 1 to the value of FMT-COUNT integer variables. At fetch time, CTBFETCH uses each variable to indicate the following conditions about the fetched data:

Value

Integer value

Meaning

CS-NULLDATA

-1

There was no data to fetch. In this case, no data is copied to the destination variable.

CS-GOODDATA

0

The fetch was successful.

n

The actual length of the server data, if the fetch resulted in truncation. n is an integer value.

If BUFFER is an array, INDICATOR will also be an array.

INDICATOR-NULL

(I) NULL indicator for INDICATOR. This argument allows you to treat INDICATOR as null (LOW-VALUES). Assign this argument one of the following values:

Value

Meaning

CS-PARAM-NULL (-102)

INDICATOR is LOW-VALUES. If INDICATOR is an array, assigning CS-PARAM-NULL to this argument causes all elements of INDICATOR to be treated as LOW-VALUES.

CS-PARAM-NOTNULL (-103)

INDICATOR is not LOW-VALUES.

Returns

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

Table 3-3: CTBBIND return values

Value

Meaning

CS-SUCCEED (-1)

The routine completed successfully.

CS-FAIL (-2)

The routine failed.

TDS-CONNECTION-TERMINATED (-4997)

The connection is not active.

TDS-INVALID-DATAFMT-VALUE (-181)

DATAFMT field contains an illegal value.

TDS-INVALID-PARAMETER (-4)

A parameter was given an illegal value.

TDS-INVALID-VAR-ADDRESS (-175)

This value cannot be NULL.

TDS-NO-COMPUTES-ALLOWED (-60)

Compute results are not supported.

TDS-RESULTS-CANCELED (-49)

A cancel was sent to purge results.

TDS-SOS (-257)

Memory shortage. The operation failed.

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 CTBBIND to set up column headings in result rows. It is taken from the sample program SYCTSAA5 in Appendix A, “Sample Language Requests.”

	*========================================================
	*==                                                    ==
	*== 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


Array binding

Array binding is the act of binding a result column to an array of program variables. At fetch time, multiple rows of the column are copied to the array of variables with a single CTBFETCH call. An application indicates array binding by assigning FMT-COUNT a value greater than 1

See also

Related functions

Related topics