CTBCONPROPS

Description

Sets or retrieves connection handle properties.

Syntax

COPY CTPUBLIC.
01 CONNECTION      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 'CTBCONPR' USING CONNECTION RETCODE ACTION PROPERTY BUFFER BUFFER-LEN BUFBLANKSTRIP OUTLEN

Parameters

CONNECTION

(I) Handle for this connection. This connection handle must already be allocated with CTBCONALLOC. The connection 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 description, 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:

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

(I/O) 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, 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, 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 you are setting a property value 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 CTBCONPROPS returns the length of the property value being retrieved.

If the retrieved information is larger than BUFFER-LEN in 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. If ACTION is CS-CLEAR or CS-SET, this value is ignored.

Returns

CTBCONPROPS returns one of the following values:

Value

Meaning

CS-SUCCEED (-1)

The routine completed successfully.

CS-FAIL (-2)

The routine failed.

TDS-CANNOT-SET-VALUE (-43)

This property cannot be set by the application.

TDS-INVALID-PARAMETER (-4)

One or more arguments contain illegal values.

Examples

Example 1

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

*========================================================
*==                                                    ==
*== Subroutine to process input data                   ==
*==                                                    ==
*========================================================
        	PROCESS-INPUT.
  
       *********************************
       * ALLOCATE A CONNECTION HANDLE. *
       *********************************
            MOVE ZERO TO CSL-CON-HANDLE.
            CALL 'CTBCONAL' USING CSL-CTX-HANDLE
                                  CSL-RC
                                  CSL-CON-HANDLE.
             IF CSL-RC NOT EQUAL CS-SUCCEED
              THEN
                 MOVE SPACES TO MSGSTR
                 STRING 'CTBCONAL failed' DELIMITED BY SIZE INTO MSGSTR
                 PERFORM PRINT-MSG
                 PERFORM ALL-DONE
            END-IF.
  
       *******************
       * SET THE USER ID *
       *******************
            CALL 'CTBCONPR' USING CSL-CON-HANDLE
                                  CSL-RC
                                  CS-SET
                                  CS-USERNAME
                                  PF-USER
                                  PF-USER-SIZE
                                  CS-FALSE
                                  OUTLEN.
            IF CSL-RC NOT EQUAL CS-SUCCEED
              THEN
                 MOVE SPACES TO MSGSTR
                 STRING 'CTBCONPR for user-id failed' DELIMITED BY SIZE
                                                      INTO MSGSTR
                 PERFORM PRINT-MSG
                 PERFORM ALL-DONE
            END-IF.
       ********************
       * SET THE PASSWORD *
       ********************
             CALL 'CTBCONPR' USING CSL-CON-HANDLE
                                  CSL-RC
                                  CS-SET
                                  CS-PASSWORD
                                  PF-PWD
                                  PF-PWD-SIZE
                                  CS-FALSE
                                  OUTLEN.
            IF CSL-RC NOT EQUAL CS-SUCCEED
              THEN
                 MOVE SPACES TO MSGSTR
                 STRING 'CTBCONPR for password failed' DELIMITED BY SIZE
                                                       INTO MSGSTR
                 PERFORM PRINT-MSG
                 PERFORM ALL-DONE
            END-IF.
       ********************
       * SET THE TRAN NAME *
       ********************
            IF PF-TRAN-SIZE IS NOT EQUAL TO ZEROES THEN
                CALL 'CTBCONPR' USING CSL-CON-HANDLE
                                      CSL-RC
                                      CS-SET
                                      CS-TRANSACTION-NAME
                                      PF-TRAN
                                      PF-TRAN-SIZE
                                      CS-FALSE
                                      OUTLEN
                IF CSL-RC NOT EQUAL CS-SUCCEED
                  THEN
                     MOVE SPACES TO MSGSTR
                     STRING 'CTBCONPR for TRAN name failed'
                            DELIMITED BY SIZE INTO MSGSTR
                     PERFORM PRINT-MSG
                     PERFORM ALL-DONE
                  END-IF
            END-IF.
       *******************************
       * SET THE NET DRIVER PROPERTY *
       *******************************
            IF PF-NETDRV = SPACES OR PF-NETDRV = 'LU62'                X
                                  OR PF-NETDRV = 'lu62'
                MOVE CS-LU62 TO NETDRIVER
            ELSE
              IF PF-NETDRV = 'IBMTCPIP' OR PF-NETDRV = 'ibmtcpip'
                MOVE CS-TCPIP TO NETDRIVER
            ELSE
              IF PF-NETDRV = 'INTERLIN' OR PF-NETDRV = 'interlin'
                MOVE CS-INTERLINK TO NETDRIVER
            ELSE
              IF PF-NETDRV = 'CPIC' OR PF-NETDRV = 'cpic'
                MOVE CS-NCPIC TO NETDRIVER
            END-IF.
            IF PF-DRV-SIZE IS NOT EQUAL TO ZEROES THEN
                CALL 'CTBCONPR' USING CSL-CON-HANDLE
                                      CSL-RC
                                      CS-SET
                                      CS-NET-DRIVER
                                      NETDRIVER
                                      CS-UNUSED
                                      CS-FALSE
                                      OUTLEN
                IF CSL-RC NOT EQUAL CS-SUCCEED
                  THEN
                     MOVE SPACES TO MSGSTR
                     STRING 'CTBCONPR for network driver failed'
                            DELIMITED BY SIZE INTO MSGSTR
                     PERFORM PRINT-MSG
                     PERFORM ALL-DONE
                  END-IF
            END-IF.
       ********************************
       * SET FOR MAINFRAME EXTRA INFO *
       ********************************
            CALL 'CTBCONPR' USING CSL-CON-HANDLE
                                  CSL-RC
                                  CS-SET
                                  CS-EXTRA-INF
                                  CS-TRUE
                                  CS-UNUSED
                                  CS-FALSE
                                  CS-UNUSED.
            IF CSL-RC NOT EQUAL CS-SUCCEED
              THEN
                 MOVE SPACES TO MSGSTR
                 STRING 'CTBCONPR for extra info failed'
                                    DELIMITED BY SIZE INTO MSGSTR
                 PERFORM PRINT-MSG
                 PERFORM ALL-DONE
            END-IF.

Usage

See also

Related functions

Related topics