CALL "A$LIST_USERS" USING LISTUSR-NEXT                             listHandle                            ID                            userName                            userAddr                            userComp                            threadID                            prog                           [type]                            [loginTime]   | 
LISTUSR-NEXT   | Constant   | |
listHandle   | USAGE HANDLE   | Specifies the handle of a list returned by the LISTUSR-OPEN function  | 
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.  | 
threadID  | PIC 9(n)  | Receives the unique thread ID of the client. The returned value is between 1 and 2147483647.   | 
prog  | PIC X(n)  | Receives the name of the program launched by the client or the name of the last program called through the 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 - standard isCOBOL Client 1 -  webClient 2 - client running in a separate process due to the iscobol.as.multitasking setting  | 
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.  | 
0   | No more items available.  | 
>0  | Information returned correctly.  |