CTBREMOTEPWD

Description

Defines or clears passwords to be used for server-to-server connections.

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 SERVERNAME           PIC X(30).
01 SRV-LEN              PIC S9(9) COMP SYNC.
01 SRV-BLANKSTRIP       PIC S9(9) COMP SYNC.
01 PASSWD               PIC X(30).
01 PWD-LEN              PIC S9(9) COMP SYNC.
01 PWD-BLANKSTRIP       PIC S9(9) COMP SYNC.
CALL 'CTBREMOT' USING CONNECTION RETCODE ACTION SERVERNAME SRV-LEN SRV-BLANKSTRIP PASSWD PWD-LEN PWD-BLANKSTRIP.

Parameters

CONNECTION

(I) Handle for this connection. This connection handle must already be allocated with CTBCONALLOC.

Remote passwords can only be defined for a connection before it is open. Passwords defined after a connection is open are ignored.

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. ACTION can be any of the following symbolic values:

Value

Meaning

CS-SET (34)

Sets the remote password.

CS-CLEAR (35)

Clears all remote passwords specified for this connection by assigning LOW-VALUES to SERVERNAME and PASSWD.

SERVERNAME

(I) Name of the server for which the password is being defined. This is the name by which the server is known in the Server Path Table.

If ACTION is CS-CLEAR, SERVERNAME will default to LOW-VALUES.

If SERVERNAME is LOW-VALUES, the specified password will be considered a “universal” password, to be used with any server that does not have a password explicitly specified for it.

SERVERNAME-LEN

(I) Length, in bytes, of SERVERNAME. To use the default “universal” password, assign CS-NULL-STRING to this argument. To indicate that the value is terminated at the last non-blank character, assign CS-TRUE to SRVBLANKSTRIP.

SRVBLANKSTRIP

(I) Blank termination indicator. Indicates whether the value in the buffer is terminated at the last non-blank character. 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.

PASSWD

(I) Password being installed for remote logins to the server named in SERVERNAME.

If ACTION is CS-CLEAR, PASSWD is passed as LOW-VALUES, and the password defaults to the one set for this connection in CTBCONPROPS, if any.

PASSWD-LEN

(I) Length, in bytes, of PASSWD. To indicate that the value is terminated at the last non-blank character, assign CS-TRUE to PWDBLANKSTRIP.

PWDBLANKSTRIP

(I) Blank stripping indicator. Indicates whether the value of the password is terminated at the last non-blank character.

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.

Returns

CTBREMOTEPWD returns one of the following values:

Value

Meaning

CS-SUCCEED (-1)

Results are available for processing.

CS-FAIL (-2)

The routine failed.

TDS-INVALID-PARAMETER (-4)

One or more of the CTBREMOTEPWD arguments contains an illegal value.

Likely causes for this code are:

  • Erroneous value for ACTION. ACTION cannot be CS-GET for CTBREMOTEPWD.

  • Erroneous value for a length argument. Length values cannot be negative numbers.

TDS-SOS (-257)

Memory shortage. The operation failed.

Examples

Example 1

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

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 RETCODE                      PIC S9(9) COMP SYNC VALUE +0.
	01 USER                         PIC X(30).
	01 REM-PWD                      PIC X(30).
	01 REM-PWD-LEN                  PIC S9(9) COMP SYNC VALUE IS 0.   
	01 STRLEN                       PIC S9(9) COMP SYNC.
	01 SERVNAME                     PIC X(30).
	01 USER-DATA                    PIC X(30).
    01 I                            PIC S9(9) COMP SYNC.
    01 I2                           PIC S9(9) COMP SYNC VALUE IS 0.
    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.   
    
    PROCEDURE DIVISION.
    P0.
* SET THE REMOTE PASSWORD
 
      MOVE LOW-VALUES TO SERVNAME.
      STRING 'server2' DELIMITED BY SIZE INTO SERVNAME.
      MOVE 7  TO STRLEN.
      STRING 'passwd2' DELIMITED BY SIZE INTO REM-PWD.
      MOVE 7  TO REM-PWD-LEN.
      CALL 'CTBREMOT' USING CON RETCODE CS-SET SERVNAME STRLEN
                      CS-FALSE  REM-PWD REM-PWD-LEN CS-FALSE.
      IF RETCODE NOT EQUAL CS-SUCCEED
          MOVE SPACES TO MSGSTR
           STRING 'CTBREMOT FAILED' DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG.
 
      MOVE LOW-VALUES TO REM-PWD.
      CALL 'CTBREMOT' USING CON RETCODE CS-GET SERVNAME STRLEN
                      CS-FALSE  REM-PWD REM-PWD-LEN CS-FALSE.
      IF RETCODE NOT EQUAL CS-SUCCEED
          MOVE SPACES TO MSGSTR
           STRING 'CTBREMOT FAILED' DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG.
 
      MOVE LOW-VALUES TO SERVNAME.
      STRING 'mystring-sun4' DELIMITED BY SIZE INTO SERVNAME.
      MOVE 10 TO STRLEN.
      CALL 'CTBCONNE' USING CON RETCODE SERVNAME STRLEN CS-FALSE.
      IF RETCODE NOT EQUAL CS-SUCCEED
          MOVE SPACES TO MSGSTR
           STRING 'CTBCONNE FAILED' DELIMITED BY SIZE INTO MSGSTR
          PERFORM PRINT-MSG
          PERFORM ALLDONE.

Usage

See also

Related functions