CTBPARAM

Description

Defines a command parameter.

Syntax

COPY CTPUBLIC. 
01 COMMAND    PIC S9(9) COMP SYNC. 
01 RETCODE    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 DATA         type 
01 DATALEN      PIC S9(9) COMP SYNC. 
01 INDICATOR    PIC S9(4) COMP SYNC.
CALL 'CTBPARAM' USING COMMAND RETCODE DATAFMT DATA DATALEN INDICATOR.

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.

DATAFMT

(I) A structure that contains a description of the parameter. This structure is also used by CTBBIND, CTBDESCRIBE, and CSBCONVERT and is explained in “DATAFMT structure”.

Table 3-13 lists the fields in the DATAFMT structure, indicates whether or when they are used by CTBPARAM, and contains general information about the fields.

For specific information on how to set these fields when defining a parameter for a particular kind of command, see the charts in Table 3-13.

NoteThe programmer is responsible for adhering to these rules. Client-Library does not enforce them.

Table 3-13: Fields in the DATAFMT structure for CTBPARAM

When this field

Is used in this condition

Set the field to

FMT-NAME

When defining parameters for all supported commands.

The name of the parameter being defined.

If FMT-NAMELEN is 0, the parameter is considered to be unnamed. Unnamed parameters are interpreted positionally. It is an error to mix named and unnamed parameters in a single command.

NoteWhen sending parameters to an Adaptive Server, FMT-NAME must begin with the “@” symbol, which prefixes all Adaptive Server stored procedure parameter names.

When sending parameters with language requests, this must be the variable name as it appears in the language string. Transact-SQL names begin with the colon (:) symbol.

FMT-NAMELEN

When defining parameters for all supported commands.

The length, in bytes, of FMT-NAME.

If FMT-NAMELEN is 0, the parameter is considered to be unnamed.

FMT-TYPE

When defining parameters for all supported commands.

The datatype of the parameter value. All datatypes listed under “Datatypes” are valid.

FMT-FORMAT

Not used (CS-FMT-UNUSED).

Not applicable.

FMT-MAXLEN

When defining non-fixed-length return parameters for RPCs; otherwise CS-UNUSED.

The maximum length, in bytes, of the data returned in this parameter.

For character or binary data, FMT-MAXLEN must represent the total length of the return parameter, including any space required for special terminating bytes, with this exception: when the parameter is a VARYCHAR datatype such as the DB2 VARCHAR, FMT-MAXLEN does not include the length of the “LL” length specification.

For Sybase-decimal and Sybase-numeric, set FMT-MAXLEN to 35.

If the parameter is non-return, if FMT-TYPE is fixed-length, or if the application does not need to restrict the length of return parameters, set FMT-MAXLEN to CS-UNUSED.

FMT-SCALE

Used for packed decimal, Sybase-decimal, and Sybase-numeric datatypes.

The number of digits after the decimal point.

FMT-PRECIS

Used for packed decimal, Sybase-decimal, and Sybase-numeric datatypes.

The total number of digits before and after the decimal point.

FMT-STATUS

When defining parameters for all types of commands except message commands.

The type of parameter being defined. One of the following values:

  • CS-INPUTVALUE - The parameter is an input parameter value for a non-return RPC parameter or a language request parameter.

  • CS-RETURN - The parameter is a return parameter.

FMT-COUNT

Not used (CS-FMT-UNUSED).

Not applicable.

FMT-UTYPE

Only when defining a parameter that has an Adaptive Server user-defined datatype; otherwise CS-UNUSED.

The user-defined datatype of the 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

Not used (CS-FMT-UNUSED).

LOW-VALUES.

DATA

Variable that contains the parameter data.

To indicate a parameter value of LOW-VALUES, assign INDICATOR a value of -1.

If INDICATOR is -1, DATA and DATA-LEN are ignored. For example, an application might pass null parameters (containing LOW-VALUES) to a stored procedure or transaction that assigns default values to null input parameters.

DATA-LEN

The length, in bytes, of the parameter data. For Sybase-numeric and Sybase-decimal, set DATA-LEN to 35.

INDICATOR

An integer variable used to indicate a parameter value of LOW-VALUES. To indicate that a parameter is null, assign INDICATOR a value of -1. If INDICATOR is -1, DATA and DATA-LEN are ignored.

Returns

CTBPARAM returns one of the following values:

Value

Meaning

CS-SUCCEED (-1)

The routine completed successfully.

CS-FAIL (-2)

The routine failed.

Examples

Example 1

The following code fragment illustrates the use of CTBPARAM. It is taken from the sample program SYCTSAR5 in Appendix B, “Sample RPC Application.”

 ************************************************************
* INITIATE THE STORED PROCEDURE "SYR2". THE DATA WILL BE    *
* RETURNED FROM THE TABLE SYBASE.SAMPLETB. THIS CAN EITHER  *
* BE A DB2 OR AN Adaptive SERVER TABLE DEPENDING  ON WHETHER*
* THE RPC IS SENT TO A CICS REGION OR A Adaptive SERVER.    *
 ************************************************************
  
      MOVE LOW-VALUES TO CMDSTR.
      MOVE 4          TO INTARG.
      STRING 'SYR2' DELIMITED BY SIZE INTO CMDSTR.
  
      CALL 'CTBCOMMA' USING CSL-CMD-HANDLE
                            CSL-RC
                            CS-RPC-CMD
                            CMDSTR
                            INTARG
                            CS-UNUSED.
  
      IF CSL-RC NOT EQUAL CS-SUCCEED
        THEN
          MOVE SPACES TO MSGSTR
          STRING 'CTBCOMMAND failed'
                 DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG
          PERFORM ALL-DONE
      END-IF.
  
 *****************************
 * SET UP THE RPC PARAMETERS *
 *****************************
  
      MOVE '@parm1'        TO NM-PARM.
      MOVE 6               TO NMLEN-PARM.
      MOVE CS-FMT-NULLTERM TO FORMT-PARM.
      MOVE CS-RETURN       TO FMTSTATUS-PARM.
      MOVE CS-INT-TYPE     TO DATATYPE-PARM.
      MOVE LENGTH OF PARM1 TO DATALEN.
      MOVE 0               TO PARM1.
  
      CALL 'CTBPARAM' USING CSL-CMD-HANDLE
                            CSL-RC
                            DATAFMT-PARM
                            PARM1
                            DATALEN
                            INDIC.
  
      IF CSL-RC NOT EQUAL CS-SUCCEED
        THEN
          MOVE SPACES TO MSGSTR
          STRING 'CTBPARAM CS-INT-TYPE parm1 failed'
                 DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG
          PERFORM ALL-DONE
      END-IF.
  
      MOVE '@parm2'           TO NM-PARM.
      MOVE 6                  TO NMLEN-PARM.
      MOVE CS-FMT-NULLTERM    TO FORMT-PARM.
      MOVE CS-INPUTVALUE      TO FMTSTATUS-PARM.
      MOVE CS-VARCHAR-TYPE    TO DATATYPE-PARM.
      MOVE PF-DEPT            TO PARR-RET.
      MOVE PF-DEPT-SIZE       TO DATALEN.
      MOVE 255                TO MAXLENGTH-PARM.
  
      CALL 'CTBPARAM' USING CSL-CMD-HANDLE
                            CSL-RC
                            DATAFMT-PARM
                            PARM2
                            DATALEN
                            INDIC.
  
      IF CSL-RC NOT EQUAL CS-SUCCEED
        THEN
          MOVE SPACES TO MSGSTR
          STRING 'CTBPARAM CS-VARCHAR-TYPE parm2 failed'
                 DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG
          PERFORM ALL-DONE
      END-IF.
  
 ***************************************
 * SEND THE COMMAND AND THE PARAMETERS *
 ***************************************
  
      CALL 'CTBSEND' USING CSL-CMD-HANDLE
                           CSL-RC.
  
      IF CSL-RC NOT EQUAL CS-SUCCEED
        THEN
          MOVE SPACES TO MSGSTR
          STRING 'CTBSEND failed'
                 DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG
          PERFORM ALL-DONE
      END-IF.
  
  SEND-PARAM-EXIT.
      EXIT.
  

Usage


Defining arguments for language requests

An application calls CTBPARAM with FMT-STATUS as CS-INPUTVALUE to define a parameter value for a language request containing variables.

The following fields in the DATAFMT structure take special values when describing a parameter for a language request. These are listed in Table 3-14.

Table 3-14: DATAFMT fields for language request parameters with CTBPARAM

Field

Value

NAME

The variable name as it appears in the language string. Transact-SQL names begin with the colon (:) character.

FMT-STATUS

CS-INPUTVALUE

All other fields

Standard CTBPARAM values.


Defining arguments for RPCs

An application calls CTBPARAM with FMT-STATUS as CS-RETURN to define a return parameter for an RPC, and calls CTBPARAM with FMT-STATUS as CS-INPUTVALUE to define a non-return parameter.

Table 3-15: DATAFMT fields for RPC parameters with CTBPARAM

Field

Value

FMT-NAME

When sending parameters to an Adaptive Server, FMT-NAME must begin with the “@” symbol, which prefixes all Adaptive Server stored procedure parameter names.

FMT-MAXLEN

The maximum length of data to be returned by the server.

Set to CS-UNUSED if the parameter is non-return, if FMT-TYPE is fixed-length, or if the application does not need to restrict the length of return parameters.

FMT-STATUS

CS-RETURN to indicate that the parameter is a return parameter.

CS-INPUTVALUE to indicate that the parameter is not a return parameter.

All other fields

Standard CTBPARAM values.

Table 3-16 lists a summary of arguments for CTBPARAM.

Table 3-16: Summary of arguments (CTBPARAM)

Command

FMT-STATUS value

DATA, DATA-LEN value

Language request

CS-INPUTVALUE

The parameter value and length.

RPC (return parameters)

CS-RETURN

The parameter value and length.

RPC (non-return parameters)

CS-INPUTVALUE

The parameter value and length.

See also

Related functions