CALL "A$GET_USER" USING threadID ID userName userAddr userComp prog [type] [loginType] [userInfo] GIVING returnCode |
threadID | PIC 9(n) | Specifies the threadID to query |
ID | PIC S9(n) | Receives the user ID. If it is zero, it means that the user is an administrator, if it is –1, it means that no login has been made |
userName | PIC X(n) | Receives the user name. If no login has been made, it’s set to the operating system user name |
userAddr | PIC X(n) | Receives the IP address of the client machine[*] |
userComp | PIC X(n) | Receives the name of the client machine[*]. If the computer name can’t be retrieved, the IP address is returned in this field. |
prog | PIC X(n) | Receives the name of the program launched by the client or the name of the last program called through CHAIN statement. The special value "File server" identifies a connection to the isCOBOL File Server. The special value "Server Call Session" identifies a remote call. The text between square brackets tells the name of the program that was remotely called. See Remote objects for details. |
type | PIC 9(1) | Optional parameter. Returns the client type. The value is the sum between one or more of these values: 0 - Thin client, FileServer client or remote call 1 - WebClient 2 - Thin client running in a separate process due to the iscobol.as.multitasking setting 3 - WebClient running in a separate process due to the iscobol.as.multitasking setting 4 - TurboRun session |
loginTime | PIC X(16) | Optional parameter. Returns the date and time the client session was started. The information is returned in the format YYYYMMDDHHNNSSCC, where YYYY is the year, MM is the month (1-12), DD is the day in the month (1-31), HH is the number of hours (0-24), NN is the number of minutes (0-59), SS is the number of seconds (0-59) and CC is the number of hundreds of seconds (0-99). The time is returned in the UTC time zone. |
userInfo | PIC X(n) | Optional parameter. Returns the custom information bound to this client session. To store custom information, call the AUSERINFO-SET function. |
0 | Operation successful |
-1 | Invalid parameters |
-2 | Invalid thread ID |
*> Define in working-storage threadID, user-id and returnCode as pic s9(n) *> and all other parameters as pic x(n) *> threadID should be sent as input parameter, all others will be *> output parameters (use a$getthread or a$list-users to obtain *> a threadID before the following call) call "a$get_user" using threadID user-id user-name user-ip-address user-computer-name user-program-name giving returnCode |