Visual Basic 6 function "GetProcessWindows"

Go back

Below you'll find the source for the Visual Basic 6 function GetProcessWindows.

Attribute VB_Name = "modGetProcessWindows"
' These functions are downloaded from:
' http://www.stefanthoolen.nl/archive/vb6-functions/
' 
' You may freely distribute this file but please leave all comments, including this one, in it.
' 
' @Author Stefan Thoolen <mail@stefanthoolen.nl>

Option Explicit

Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal Hwnd As Long, lpdwProcessId As Long) As Long

Private Declare Function GetWindow Lib "user32" (ByVal Hwnd As Long, ByVal wCmd As Long) As Long

Private Declare Function GetParent Lib "user32" (ByVal Hwnd As Long) As Long

Private Declare Function FindWindowA Lib "user32" (ByVal lpClassName As Long, ByVal lpWindowName As Long) As Long

Private Declare Function GetWindowTextA Lib "user32" (ByVal Hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Private Declare Function GetWindowTextLengthA Lib "user32" (ByVal Hwnd As Long) As Long

Private Const GW_HWNDNEXT = 2

' Own types to return information
Public Type WindowEntry
    Hwnd As Long
    Caption As String
End Type


''
' Gets a window caption
' @param    Long    Hwnd        The window handler
' @return   String              The caption of the window
' @author   Stefan Thoolen <mail@stefanthoolen.nl>
Public Function GetWindowCaption(Hwnd As Long) As String
    Dim l As Long, s As String
    
    l = GetWindowTextLengthA(Hwnd) + 1
    s = String(l, 0)
    GetWindowTextA Hwnd, s, l
    
    GetWindowCaption = Left(s, InStr(s, vbNullChar) - 1)
End Function

''
' Returns all kind of Window-information of a process
' Example:
'    Dim we() As WindowEntry
'    GetProcessWindows pid, we
'
' @param    Long    processID       The process ID
' @param    WindowEntry arr         An entry containing all information of the window
' @return   Void
' @author   Stefan Thoolen <mail@stefanthoolen.nl>
Public Sub GetProcessWindows(processID As Long, ByRef arr() As WindowEntry)
    Dim tmp_hwnd As Long, hwnd_cnt As Integer: hwnd_cnt = -1
    Dim tmp_pid As Long
    Dim tmp_thread_id As Long
    tmp_hwnd = FindWindowA(ByVal 0&, ByVal 0&)
    Do While tmp_hwnd <> 0
        If GetParent(tmp_hwnd) = 0 Then
            tmp_thread_id = GetWindowThreadProcessId(tmp_hwnd, tmp_pid)
            If tmp_pid = processID Then
                hwnd_cnt = hwnd_cnt + 1
                ReDim Preserve arr(0 To hwnd_cnt)
                arr(hwnd_cnt).Hwnd = tmp_hwnd
                arr(hwnd_cnt).Caption = GetWindowCaption(tmp_hwnd)
            End If
        End If
        tmp_hwnd = GetWindow(tmp_hwnd, GW_HWNDNEXT)
    Loop
End Sub