TDGETUSR

Description

Gets user login information from the client.

Syntax

COPY SYGWCOB.
01 TDPROC             PIC S9(9)  USAGE COMP SYNC.
01 RETCODE            PIC S9(9)  USAGE COMP SYNC.
01 ACCESS-CODE        PIC X(32).
01 USER-ID            PIC X(32).
01 PASSWORD           PIC X(32).
01 SERVER-NAME        PIC X(32).
01 CLIENT-CHARSET     PIC X(32).
01 NATIONAL-LANGUAGE  PIC X(32).
01 SERVER-CHARSET     PIC X(32).01 SERVER-DBCS        PIC X(32).
01 APPNAME-ID         PIC X(32).CALL 'TDGETUSR' USING TDPROC, 

RETCODE, ACCESS-CODE, 
               USER-ID, PASSWORD, SERVER-NAME,
               CLIENT-CHARSET, NATIONAL-LANGUAGE, 
               SERVER-CHARSET, SERVER-DBCS,
                 APPNAME-ID.

Parameters

TDPROC

(I) Handle for this client/server connection. This must be the same value specified in the associated TDACCEPT call. The TDPROC handle corresponds to the connection and command handles in Open Client Client-Library.

RETCODE

(O) Variable where the result of function execution is returned. Its value is one of the codes listed in Table 3-11.

ACCESS-CODE

(I) Variable containing an access code that authorizes this application to retrieve a client password. TDGETUSR gets this information from the mainframe customization module.

USER-ID

(O) Variable where the client user ID is returned to the application. This is the user ID the client uses to log into the TRS.

PASSWORD

(O) Variable where the client password is returned to the application. This is the password the client uses when logging into the TRS.

NoteIf an access code is required and it does not match the access code specified during mainframe customization, the PASSWORD field is set to blanks.

SERVER-NAME

(O) Variable where the name of the server specified by the client is returned. For workstation clients, this is the name of the TRS used to access this Open ServerConnect application.

CLIENT-CHARSET

(O) Variable where the name of the character set used by the client is returned. This information is provided in the client login packet.

NATIONAL-LANGUAGE

(O) Variable where the name of the national language used by the client is returned. This information is provided in the client login packet. If no national language is specified, the default is U.S. English.

SERVER-CHARSET

(O) Variable where information about the treatment of single-byte characters is returned. This value is set during customization.

If SERVER-DBCS indicates that double-byte character sets are not supported (SERVER-DBCS is NONE), SERVER-CHARSET returns the name of the default single-byte character set used by Gateway-Library programs. The default character set is used in the following cases:

  • The client login packet does not specify a character set.

  • The client login packet specifies a character set, but Gateway-Library cannot find that character set in the table of character set names.

If SERVER-DBCS indicates that double-byte character sets are supported (SERVER-DBCS is KANJI), SERVER-CHARSET indicates how single-byte characters are treated.

Single-byte characters can be treated as either:

LOWERCASE

Lowercase letters (roman alphabet)

KANA

Hankaku katakana (single-byte Japanese characters)

SERVER-DBCS

(O) DBCS support indicator. This value indicates whether the mainframe system is using double-byte kanji characters or only single-byte characters. TDGETUSR gets this information from the mainframe customization module.

KANJI

Double-byte characters are supported.

NONE

Double-byte characters are not supported.

APPNAME-ID

(O) Name of the client application (from the client login record). The application name is set on the client side via a dbsetlapp call, and forwarded to the mainframe by the TRS. APPNAME-ID is typically used to pass unique identifier information about the client application.

Returns

The RETCODE argument can contain any of the return values listed in Table 3-11.

Table 3-11: TDGETUSR return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CONNECTION-TERMINATED (-4997)

Connection closed. The remote partner closed (deallocated) the client/server connection.

TDS-INVALID-PARAMETER (-4)

Invalid parameter value. The value assigned to one or more of the arguments supplied in the call is not valid. The operation failed.

TDS-INVALID-TDPROC (-18)

Error in specifying a value for the TDPROC argument.

Examples

Example 1

The following code fragment illustrates the use of TDGETUSR to verify the client login information. The program must provide an access code—TOP SECRET—for permission to access the user’s password. This example is taken from the sample program, SYCCSAR2, in Appendix B, “Sample RPC Application for CICS.”

 *    Accept client request
 
      CALL 'TDACCEPT' USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,
                            SNA-CONNECTION-NAME, SNA-SUBC.
 
 *    TDRESULT to make sure we were started via RPC request
 
      CALL 'TDRESULT' USING GWL-PROC, GWL-RC.
 
      IF GWL-RC NOT = TDS-PARM-PRESENT THEN
          PERFORM TDRESULT-ERROR
          GO TO END-PROGRAM
      END-IF.
 
 *    Verify user login information
 
      MOVE 'TOP SECRET' TO GU-ACCESS-CODE.
 
      CALL 'TDGETUSR'  USING GWL-PROC, GWL-RC, GU-ACCESS-CODE,
                   GU-USER-ID, GU-PASSWORD, GU-SERVER-NAME,
                   GU-CLIENT-CHARSET, GU-NATIONAL-LANG,
                   GU-SERVER-CHARSET, GU-SERVER-DBCS, GU-APP-ID.
 
      IF GWL-RC  NOT = TDS-OK THEN
          PERFORM TDGETUSR-ERROR
          GO TO END-PROGRAM
       END-IF.

Usage

NoteYou can deactivate this feature, allowing the program to retrieve the password without an access code.

See also

Related functions

Related topics