CTBCMDPROPS

Description

Sets, retrieves, or clears information about the current result set.

Syntax

COPY CTPUBLIC.
01 COMMAND PIC S9(9) COMP SYNC.
01 RETCODE PIC S9(9) COMP SYNC.
01 ACTION  PIC S9(9) COMP SYNC.
01 PROPERTY PIC S9(9) COMP SYNC.
01 BUFFER type.
01 BUFFER-LEN  PIC S9(9) COMP SYNC.
01 BUFBLANKSTRIP PIC S9(9) COMP SYNC.
01 OUTLEN  PIC S9(9) COMP SYNC.
CALL 'CTBCMDPR' USING COMMAND RETCODE ACTION PROPERTY BUFFER-LEN BUFBLANKSTRIP OUTLEN.

Parameters

COMMAND

(I) Handle for this client/server operation. This handle is defined in the associated CTBCMDALLOC call. 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.

ACTION

(I) Action to be taken by this call. ACTION is an integer variable that indicates the purpose of this call.

Assign ACTION one of the following symbolic values

Value

Meaning

CS-GET (33)

Retrieves the value of the property.

CS-SET (34)

Sets the value of the property.

CS-CLEAR (35)

Clears the value of the property by resetting the property to its Client-Library default value.

PROPERTY

(I) Symbolic name of the property for which the value is being set or retrieved. Client-Library properties are listed under “Properties”, with descriptions, possible values, and defaults.

BUFFER

(I/O) Variable (buffer) that contains the specified property value.

If ACTION is CS-SET, the buffer contains the value used by CTBCMDPROPS.

If ACTION is CS-GET, CTBCMDPROPS returns the requested information to this buffer.

If ACTION is CS-CLEAR, the buffer is reset to the default property value.

This argument is typically one of the following datatypes:

	PIC S9(9) COMP SYNC.
	PIC X(n).
BUFFER-LEN

(I) Length, in bytes, of the buffer.

If ACTION is CS-SET and the value in the buffer is a fixed-length or symbolic value, BUFFER-LEN should have a value of CS-UNUSED. To indicate that the terminating character is the last non-blank character, set BUFBLANKSTRIP to CS-TRUE.

If ACTION is CS-GET and BUFFER is too small to hold the requested information, CTBCMDPROPS sets OUTLEN to the length of the requested information and returns CS-FAIL. To retrieve all the requested information, change the value of BUFFER-LEN to the length returned in OUTLEN and rerun the application.

If ACTION is CS-CLEAR, set this value to CS-UNUSED.

BUFBLANKSTRIP

(I) Blank stripping indicator. Indicates whether or not trailing blanks are stripped.

Assign this argument one of the following symbolic values:

Value

Meaning

CS-TRUE (1)

Trailing blanks are stripped. The value in the buffer ends at the last non-blank character.

CS-FALSE (0)

Trailing blanks are not stripped. They are included in the value.

If a property value is being set and the terminating character is the last non-blank character, assign CS-TRUE to BUFBLANKSTRIP.

OUTLEN

(O) Length, in bytes, of the retrieved information. OUTLEN is an integer variable where CTBCMDPROPS returns the length of the property value being retrieved.

When the retrieved information is larger than BUFFER-LEN bytes, an application uses the value of OUTLEN to determine how many bytes are needed to hold the information.

OUTLEN is used only when ACTION is CS-GET. When ACTION is CS-CLEAR or CS-SET, this value is ignored.

Returns

CTBCMDPROPS returns one of the following values:

Value

Meaning

CS-SUCCEED (-1)

The routine completed successfully.

CS-FAIL (-2)

The routine failed.

TDS-INVALID-PARAMETER (-4)

One or more arguments were given illegal values.

TDS-CANNOT-SET-VALUE (-43)

This property cannot be set by the application.

Examples

Example 1

The following code fragment demonstrates the use of CTBCMDPROPS. This sample is not part of any sample program, so the Working Storage section is included.

      PROCEDURE DIVISION.
    01 CTX            PIC S9(9) COMP SYNC VALUE +0.
    01 CON            PIC S9(9) COMP SYNC VALUE +0.
    01 CMD            PIC S9(9) COMP SYNC VALUE +0.
    01 RET            PIC S9(9) COMP SYNC VALUE +0.
    01 RETCODE        PIC S9(9) COMP SYNC VALUE +0.
    01 CMDSTR         PIC X(200).
    01 PARM1          PIC X(3).   
    01 STRLEN         PIC S9(9) COMP SYNC.
    01 OUTLEN         PIC S9(9) COMP SYNC.
    01 USER-DATA      PIC X(30).
    01 USER-BUF       PIC X(8).
    01 I              PIC S9(9) COMP SYNC.
    01 DISP-MSG.
       05 TEST-CASEPIC X(10) VALUE IS 'RPC SAMPLE'.
       05 FILLERPIC X(4) VALUE IS SPACES.
       05 MSG.
          10 SAMP-LIT         PIC X(3).
          10 SAMP-RC          PIC -ZZZ9.
          10 FILLER           PIC X(3) VALUE IS SPACES.
          10 MSGSTR           PIC X(40) VALUE IS SPACES.   
       PROCEDURE DIVISION.
    P0.
 * NOW GET A COMMAND HANDLE.
      MOVE ZERO TO CMD.
      CALL 'CTBCMDAL' USING CON RETCODE CMD.
      IF RETCODE NOT EQUAL CS-SUCCEED
           MOVE SPACES TO MSGSTR
           STRING 'CTBCMDAL FAILED' DELIMITED BY SIZE INTO MSGSTR
           PERFORM PRINT-MSG
           PERFORM ALLDONE.
 * SET COMMAND PROPERTIES.
      STRING 'userdata' DELIMITED BY SIZE INTO CMDSTR.
      MOVE 8 TO STRLEN.
      CALL 'CTBCMDPR'   USING CMD RETCODE CS-SET CS-USERDATA
                        USER-DATA  STRLEN CS-FALSE OUTLEN.
          [check return code]                                                    
       
     CALL 'CTBCMDPR'   USING CMD RETCODE CS-GET CS-USERDATA
                        USER-BUF  STRLEN CS-FALSE OUTLEN.
          [check return code]                                                    
       
IF USER-DATA NOT EQUAL USER-BUF
      MOVE SPACES TO MSGSTR
      STRING 'CTBCMDPR RETURNED THE WRONG USER VALUE'
             DELIMITED BY SIZE INTO MSGSTR
      PERFORM PRINT-MSG.

Usage

See also

Related functions

Related topics