• Welcome to Powerbasic Museum 2020-B.
 

WTSENumerate Sessions, Windowstations and desktops ...

Started by Theo Gottwald, March 30, 2012, 10:20:15 PM

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

Theo Gottwald

Ok, again i have decided to open a very advanced topic.
Something that we have zero or near to zero PB Source codes around.

Nothing easy, nothing we have any source code for, even in the PB Forum.
Something that will make you to look into new areas of programming.
Areas that you may never have never set an leg before.

Did you know that Freeware remote-control software like VNC is not "sessiuon-aware" and therefore will only run in "Session 0"?
Did you know that a screensaver is a "desktop"?

You do not understand what i am talking about?

Its something thats far over what the average PB Programmer does. I am talking from:

WTSSessions, WindowStations and Desktops.

Click here for some more Infos.

Take a peek into in most advanced and basic windows programming.

My idea for this project is, to make something with Desktops, Sessions and WIndowstations.
How about a Desktops-Manager?

And here is another source code that can be converted to PowerBasic, this time by somebody who knows Visual Basic (can't be me).

Source is MSDN.

Option Explicit

Private Const WTS_CURRENT_SERVER_HANDLE = 0&

Private Enum WTS_CONNECTSTATE_CLASS
    WTSActive
    WTSConnected
    WTSConnectQuery
    WTSShadow
    WTSDisconnected
    WTSIdle
    WTSListen
    WTSReset
    WTSDown
    WTSInit
End Enum

Private Type WTS_SESSION_INFO
    SessionID As Long
    pWinStationName As Long
    state As WTS_CONNECTSTATE_CLASS
End Type

Private Declare Function WTSEnumerateSessions _
    Lib "wtsapi32.dll" Alias "WTSEnumerateSessionsA" ( _
    ByVal hServer As Long, ByVal Reserved As Long, _
    ByVal Version As Long, ByRef ppSessionInfo As Long, _
    ByRef pCount As Long _
    ) As Long
   
Private Declare Sub WTSFreeMemory Lib "wtsapi32.dll" ( _
    ByVal pMemory As Long)

Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _
    Destination As Any, Source As Any, ByVal length As Long)

Private Declare Function lstrlenA Lib "kernel32" ( _
    ByVal lpString As String) As Long

Private Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" ( _
    ByVal lpString1 As String, ByVal lpString2 As Long) As Long

Private arrWTSSessions() As WTS_SESSION_INFO

Private Function GetWTSSessions() As WTS_SESSION_INFO()
    Dim RetVal As Long
    Dim lpBuffer As Long
    Dim Count As Long
    Dim p As Long
    Dim arrSessionInfo() As WTS_SESSION_INFO
   
    RetVal = WTSEnumerateSessions(WTS_CURRENT_SERVER_HANDLE, _
                                   0&, _
                                   1, _
                                   lpBuffer, _
                                   Count)
    If RetVal Then
        ' WTSEnumerateProcesses was successful.
       
        p = lpBuffer
        ReDim arrSessionInfo(Count - 1)
        CopyMemory arrSessionInfo(0), ByVal p, _
           Count * LenB(arrSessionInfo(0))
        ' Free the memory buffer.
        WTSFreeMemory lpBuffer
   
     Else
        ' Error occurred calling WTSEnumerateProcesses.
        ' Check Err.LastDllError for error code.
        MsgBox "An error occurred calling WTSEnumerateProcesses.  " & _
        "Check the Platform SDK error codes in the MSDN Documentation " & _
        "for more information.", vbCritical, "ERROR " & Err.LastDllError
    End If
    GetWTSSessions = arrSessionInfo
End Function

Private Sub Command1_Click()
    Dim i As Integer
   
    arrWTSSessions = GetWTSSessions
    For i = LBound(arrWTSSessions) To UBound(arrWTSSessions)
        Debug.Print "Session ID: " & arrWTSSessions(i).SessionID
        Debug.Print "Machine Name: " & _
           PointerToStringA(arrWTSSessions(i).pWinStationName)
        Debug.Print "Connect State: " & arrWTSSessions(i).state
        Debug.Print "***********"
    Next i
End Sub

Public Function PointerToStringA(ByVal lpStringA As Long) As String
   Dim nLen As Long
   Dim sTemp As String

   If lpStringA Then
      nLen = lstrlenA(ByVal lpStringA)
      If nLen Then
         sTemp = String(nLen, vbNullChar)
         lstrcpy sTemp, ByVal lpStringA
         PointerToStringA = sTemp
      End If
   End If
End Function

Pierre Bellisle

#1
Hey Theo,

Here's one to play with, done with CC 4.04...

Pierre

#COMPILE EXE '#CC 4.04#
#DIM ALL
#INCLUDE "Win32Api.inc"

%WTS_CURRENT_SERVER_HANDLE = 0

%WTSActive       = 0 'User logged on to WinStation
%WTSConnected    = 1 'WinStation connected to client
%WTSConnectQuery = 2 'In the process of connecting to client
%WTSShadow       = 3 'Shadowing another WinStation
%WTSDisconnected = 4 'WinStation logged on without client
%WTSIdle         = 5 'Waiting for client to connect
%WTSListen       = 6 'WinStation is listening for connection
%WTSReset        = 7 'WinStation is being reset
%WTSDown         = 8 'WinStation is down due to error
%WTSInit         = 9 'WinStation in initialization

'Thank to José... as always.  ;-)
TYPE WTS_SESSION_INFOA DWORD
  SessionId       AS DWORD
  pWinStationName AS ASCIIZ POINTER
  State           AS LONG
END TYPE

DECLARE FUNCTION WTSEnumerateSessionsA LIB "Wtsapi32.dll" ALIAS "WTSEnumerateSessionsA" _
(BYVAL DWORD, BYVAL DWORD, BYVAL DWORD, BYREF WTS_SESSION_INFOA, BYREF DWORD) AS LONG

DECLARE SUB WTSFreeMemory LIB "Wtsapi32.dll" ALIAS "WTSFreeMemory"(BYVAL DWORD)

GLOBAL arrWTSSessions() AS WTS_SESSION_INFOA
'______________________________________________________________________________

FUNCTION GetWTSSessions() AS LONG
LOCAL lpBuffer AS WTS_SESSION_INFOA
LOCAL p        AS DWORD POINTER
LOCAL RetVal   AS LONG
LOCAL Count    AS LONG

RetVal = WTSEnumerateSessionsA(%WTS_CURRENT_SERVER_HANDLE, 0, 1, lpBuffer, Count)

IF RetVal THEN
   PRINT "WTSEnumerateProcesses was successful..."
   PRINT "Session count is" & STR$(Count)
   p = VARPTR(lpBuffer)
   PRINT
   REDIM arrWTSSessions(0 TO Count - 1) AS WTS_SESSION_INFOA
   CopyMemory(VARPTR(arrWTSSessions(0)), @p, Count * SIZEOF(WTS_SESSION_INFOA))
   WTSFreeMemory(P) 'Free the memory buffer.
ELSE
   'Error occurred calling WTSEnumerateProcesses, check Err.LastDllError for error code.
   MessageBox(%HWND_DESKTOP, "An error occurred calling WTSEnumerateProcesses.  " & $CRLF & _
              "Check the Platform SDK error codes in the MSDN Documentation "     & $CRLF & _
              "for more information.", "GetWTSSessions", %MB_ICONINFORMATION OR %MB_OK)
END IF

END FUNCTION
'______________________________________________________________________________

FUNCTION PointerToString(BYVAL lpStringA AS DWORD) AS STRING
LOCAL nLen  AS DWORD
LOCAL sTemp AS STRING

IF lpStringA THEN
   nLen = lstrlen(BYVAL lpStringA)
   IF nLen THEN
     sTemp = NUL$(nLen)
     lstrcpy(BYVAL STRPTR(sTemp), BYVAL lpStringA)
     FUNCTION = sTemp
   END IF
END IF

END FUNCTION
'______________________________________________________________________________

FUNCTION PBMAIN() AS LONG
LOCAL i AS LONG

GetWTSSessions
PRINT "----------------------------"
FOR i = LBOUND(arrWTSSessions) TO UBOUND(arrWTSSessions)
   PRINT "Session ID:   "  & STR$(arrWTSSessions(i).SessionID)
   PRINT "Machine Name:  " & PointerToString(arrWTSSessions(i).pWinStationName)
   PRINT "Connect State: ";
   SELECT CASE arrWTSSessions(i).state
     CASE %WTSActive       : PRINT "(0) User logged on to WinStation"
     CASE %WTSConnected    : PRINT "(1) WinStation connected to client"
     CASE %WTSConnectQuery : PRINT "(2) In the process of connecting to client"
     CASE %WTSShadow       : PRINT "(3) Shadowing another WinStation"
     CASE %WTSDisconnected : PRINT "(4) WinStation logged on without client"
     CASE %WTSIdle         : PRINT "(5) Waiting for client to connect"
     CASE %WTSListen       : PRINT "(6) WinStation is listening for connection"
     CASE %WTSReset        : PRINT "(7) WinStation is being reset"
     CASE %WTSDown         : PRINT "(8) WinStation is down due to error"
     CASE %WTSInit         : PRINT "(9) WinStation in initialization"
     CASE ELSE             : PRINT "Ooooops!"
   END SELECT
   PRINT "----------------------------"
NEXT

PRINT : PRINT "Press any key or click to continue..." : MOUSE ON : MOUSE 3, UP : WAITKEY$

END FUNCTION
'______________________________________________________________________________
'