CSBCONFIG

Description

Sets or retrieves context structure properties.

Syntax

COPY CTPUBLIC.
01 CONTEXT 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 PIC X(n)
01 BUFFER-LEN PIC S9(9) COMP SYNC.
01 BUFBLANKSTRIP PIC S9(9) COMP SYNC.
01 OUTLEN PIC S9(9) COMP SYNC.
CALL 'CSBCONFI' USING CONTEXT RETCODE OPTION ACTION BUFFER BUFFER-LEN BUFBLANKSTRIP OUTLEN.

Parameters

CONTEXT

(I) A context structure for which the properties are being set or retrieved. The context structure is defined in the program call CSBCTXALLOC.

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 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. Table 3-19 lists the properties that can be set or retrieved by CSBCONFIG.

Table 3-19: Values for PROPERTY (CSBCONFIG)

Application action

Property

Indicates

Set, retrieve, or clear

CS-EXTRA-INF

Whether to return the extra information required when processing messages in line, using the SQLCA or SQLCODE structures.

Retrieve only

CS-VERSION

The version number of Open Client currently in use.

BUFFER

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

If ACTION is CS-SET, CSBCONFIG takes the value from this buffer.

If ACTION is CS-GET, CSBCONFIG 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:

	01 BUFFER	 PIC S9(9) COMP SYNC.
	01 BUFFER 	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, an application sets BUFBLANKSTRIP to CS-TRUE.

If ACTION is CS-GET and BUFFER is too small to hold the requested information, CSBCONFIG 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, this value is ignored.

BUFBLANKSTRIP

(I) Blank stripping indicator. Indicates whether 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 CSBCONFIG 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 the ACTION is CS-SET or CS-CLEAR, this value is ignored.

Returns

CSBCONFIG 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 of the CSBCONFIG arguments contains an illegal value.

The most likely cause for this code is that a property value is being set and the value assigned to BUFBLANKSTRIP is not CS-TRUE.

Examples

Example 1

This code fragment demonstrates the use of CSBCONFIG. It is not taken from any of the sample programs.

   	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 VERSION                       PIC S9(9) COMP SYNC VALUE IS 0.
	01 INF-VAL                       PIC S9(9) COMP SYNC VALUE IS 0.   
	01 DISP-ROW.
       05 ROW1-VAL                   PIC X(15) VALUE IS SPACES.
       05 ROW2-VAL                   PIC X(8)  VALUE IS SPACES.
       05 FILLER                     PIC X(1)  VALUE IS SPACES.
       05 ROW3-VAL                   PIC X(9)  VALUE IS SPACES.
       05 FILLER                     PIC X(4) VALUE IS SPACES.
       05 ROW4-VAL.
           49   HIGH-VAL             PIC  ZZZ,ZZZ,ZZZ.
           49   LOW-VAL              PIC  ZZ,ZZZ.99-.
       05 FILLER                     PIC X(21) VALUE IS SPACES.
    
    01 OUTLENPIC S9(9) COMP SYNC.
    01 DISP-MSG.
           05 TEST-CASE              PIC X(10) VALUE IS 'RPC SAMPLE'.
           05 FILLER                 PIC 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.
    01 DATAFMT-PARM.
           05 NM-PARM                PIC X(132).
           05 NMLEM-PARM             PIC S9(9) COMP SYNC.
           05 DATATYPE-PARM          PIC S9(9) COMP SYNC.
           05 FORMT-PARM             PIC S9(9) COMP SYNC.
           05 MAXLENGTH-PARM         PIC S9(9) COMP SYNC.
           05 SCALE-PARM             PIC S9(9) COMP SYNC.
           05 PRECISION-PARM         PIC S9(9) COMP SYNC.
           05 FNTSTATUS-PARM         PIC S9(9) COMP SYNC.
           05 FMTCOUNT-PARM          PIC S9(9) COMP SYNC.
           05 USERTYPE-PARM          PIC S9(9) COMP SYNC.
           05 LOCALE-PARM            PIC S9(9) COMP SYNC.
    01 DATAFMT-BIND.
           05 NM-BIND                PIC X(132).
           05 NMLEN-BIND             PIC S9(9) COMP SYNC.
           05 DATATYPE-BIND          PIC S9(9) COMP SYNC.
           05 FORMT-BIND             PIC S9(9) COMP SYNC.
           05 MAXLENGTH-BIND         PIC S9(9) COMP SYNC.
           05 SCALE-BIND             PIC S9(9) COMP SYNC.
           05 PRECISION-BIND         PIC S9(9) COMP SYNC.
           05 FMTSTATUS-BIND         PIC S9(9) COMP SYNC.
           05 FMTCOUNT-BIND          PIC S9(9) COMP SYNC.
           05 USERTYPE-BIND          PIC S9(9) COMP SYNC.
           05 LOCALE-BIND            PIC S9(9) COMP SYNC.
     
    PROCEDURE DIVISION.
    P0.
    * ALLOCATE A CONTEXT STRUCTURE
      MOVE ZERO TO CTX.
      MOVE LOW-VALUES TO DATAFMT-PARM DATAFMT-BIND DISP-ROW.
      CALL 'CSBCTXAL' USING CS-VERSION-100 RETCODE CTX.
      IF RETCODE NOT EQUAL CS-SUCCEED
           MOVE SPACES TO MSGSTR
           STRING 'CSBCTXAL FAILED' DELIMITED BY SIZE INTO MSGSTR
           PERFORM PRINT-MSG
           PERFORM ALLDONE.
 
 * SET THE CONTEXT STRUCTURE PROPERTY CS-EXTRA-INF
 
      CALL 'CSBCONFI'   USING CTX RETCODE CS-SET CS-EXTRA-INF
                        CS-TRUE  CS-UNUSED CS-FALSE OUTLEN.
      IF RETCODE NOT EQUAL CS-SUCCEED
           MOVE SPACES TO MSGSTR
           STRING 'CSBCONFIG FAILED' DELIMITED BY SIZE INTO MSGSTR
           PERFORM PRINT-MSG.
 
      CALL 'CSBCONFI'   USING CTX RETCODE CS-GET CS-EXTRA-INF
                        INF-VAL  CS-UNUSED CS-FALSE OUTLEN.
      IF RETCODE NOT EQUAL CS-SUCCEED
           MOVE SPACES TO MSGSTR
           STRING 'CSBCONFIG FAILED' DELIMITED BY SIZE INTO MSGSTR
           PERFORM PRINT-MSG.
 
      IF INF-VAL NOT EQUAL CS-TRUE
           MOVE SPACES TO MSGSTR
           STRING 'CSBCONFIG RETURNED THE WRONG VALUE'
                 DELIMITED BY SIZE INTO MSGSTR.
 
      CALL 'CSBCONFI'   USING CTX RETCODE CS-GET CS-VERSION
                        VERSION CS-UNUSED CS-FALSE OUTLEN.
      IF RETCODE NOT EQUAL CS-SUCCEED
           MOVE SPACES TO MSGSTR
           STRING 'CSBCONFIG FAILED' DELIMITED BY SIZE INTO MSGSTR
           PERFORM PRINT-MSG.
 
      IF VERSION NOT EQUAL CS-VERSION-100
           MOVE SPACES TO MSGSTR
           STRING 'CSBCONFIG RETURNED THE WRONG VERSION'
                 DELIMITED BY SIZE INTO MSGSTR.
 
           PERFORM PRINT-MSG.

Usage

NoteCSBCONFIG and CTBCONFIG both set and retrieve context properties. CSBCONFIG is used with global context properties; CTBCONFIG is used with Client-Library properties.

Extra information

Version level

See also

Related functions