A$GET_USER
The A$GET_USER routine returns information about a given thread ID.
Syntax:
 CALL "A$GET_USER" USING threadID
                         ID
                         userName
                         userAddr
                         userComp
                         prog
                  GIVING returnCode
Parameters:
threadID
PIC 9(n)
Specifies the threadID to query
ID
PIC X(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.
[*] A computer may have multiple IPs and multiple alias name for the same IP too, so you might not receive the expected IP and name. Usually a safe method to get the desired information is to change the hosts configuration file (/etc/hosts on Linux/Unix, %SystemRoot%\System32\drivers\etc\hosts on Windows) appropriately.
Return code:
returnCode can be any numeric data item and provides additional information:
0
Operation successful
-1
An error occurred
Examples:
Example - Return user information given a thread Id
*> Define in working-storage threadID and returnCode as pic 9(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