Projects

Find all our projects in development below.
All source code is GNU General Public License (GPL)

Window Spy

Browsing WindowMod.bas (7.38 KB)

Attribute VB_Name = "WindowMod"
Option Explicit

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type
    
Private Type POINTAPI
    X As Long
    Y As Long
End Type

Public Type WINDOW_INFO
    EXEPath As String
    hWnd As Long
    Parent_hWnd As Long
    hInstance As Long
    ClassName As String * 100
    ModuleFilename As String * 256
    WindowCaption As String
    WindowRECT As RECT
    WindowState As Integer
    WindowEnabled As Boolean
End Type

Public Const SW_HIDE = 0
Public Const SW_NORMAL = 1
Public Const SW_MAXIMIZE = 3
Public Const SW_SHOW = 5
Public Const SW_MINIMIZE = 6
Public Const SW_RESTORE = 9

Private Const GWL_HINSTANCE = (-6)
Private Const GWL_ID = (-12)
Private Const GWL_STYLE = (-16)
Private Const HWND_TOPMOST = -1
Private Const HWND_NOTOPMOST = -2
Private Const SWP_NOACTIVATE = &H10
Private Const SWP_SHOWWINDOW = &H40
Private Const SWP_NOMOVE = &H2
Private Const SWP_NOSIZE = &H1
Private Const VK_SPACE = &H20
Private Const WM_ENABLE = &HA
Private Const WM_SETTEXT = &HC
Private Const WM_GETTEXT = &HD
Private Const WM_CLOSE = &H10
Private Const WM_GETTEXTLENGTH = &HE
Private Const WM_MOUSEMOVE = &H200
Private Const WM_LBUTTONDOWN = &H201
Private Const WM_LBUTTONUP = &H202
Private Const WM_LBUTTONDBLCLK = &H203
Private Const WM_RBUTTONDOWN = &H204
Private Const WM_RBUTTONUP = &H205
Private Const WM_RBUTTONDBLCLK = &H206
Private Const WM_KEYUP = &H101
Private Const WM_KEYDOWN = &H100
Private Const WM_COMMAND = &H111

Private Declare Function EnableWindow Lib "user32" (ByVal hWnd As Long, ByVal fEnable As Long) As Long
Private Declare Function GetClassLong Lib "user32" Alias "GetClassLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hWnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
Private Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long
Private Declare Function GetParent Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hWnd As Long, lpRect As RECT) As Long
Private Declare Function GetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long) As Long
Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Private Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hWnd As Long) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long
Private Declare Function IsIconic Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function IsWindowEnabled Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function IsZoomed Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function SendMessageByString Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As String) As Long
Private Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal Y As Long, ByVal CX As Long, ByVal CY As Long, ByVal wFlags As Long) As Long
Private Declare Function ShowWindow Lib "user32" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long
Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long

Public Function GetCaption(ByVal hWnd As Long, Optional CaptionLen As Long = -1) As String
Dim CaptionLength As Long
Dim Caption As String
    CaptionLength = GetWindowTextLength(hWnd)
    Caption = String(CaptionLength, Chr(0))
    GetWindowText hWnd, Caption, CaptionLength + 1
    If Caption = "" Then
        CaptionLength = SendMessage(hWnd, WM_GETTEXTLENGTH, 0&, 0&)
        Caption = String(CaptionLength, 0&)
        SendMessageByString hWnd, WM_GETTEXT, CaptionLength + 1, Caption
    End If
    If CaptionLen >= 0 Then CaptionLen = CaptionLength
    GetCaption = Caption
End Function


Public Function SetCaption(ByVal hWnd As Long, ByVal Caption As String) As Long
    SetCaption = SendMessageByString(hWnd, WM_SETTEXT, 0, Caption)
End Function

Public Function WindowEnabled(ByVal hWnd As Long, ByVal bOption As Boolean) As Long
    WindowEnabled = EnableWindow(hWnd, bOption)
End Function

Public Sub WindowOnTop(ByVal hWnd As Long, bOnTop As Boolean)
Dim wFlag As Long
    If bOnTop Then
        wFlag = HWND_TOPMOST
    Else
        wFlag = HWND_NOTOPMOST
    End If
    SetWindowPos hWnd, wFlag, 0, 0, 0, 0, SWP_NOACTIVATE Or SWP_NOMOVE Or SWP_NOSIZE
End Sub

Public Function SetWindowState(ByVal hWnd As Long, ByVal WindowState As Long) As Long
    SetWindowState = ShowWindow(hWnd, WindowState)
End Function

Public Sub ClickButton(ByVal hWnd As Long, Optional ClickMethod As Integer)
    Select Case ClickMethod
        Case 0
            SendMessage hWnd, WM_KEYDOWN, VK_SPACE, vbNullString
            SendMessage hWnd, WM_KEYUP, VK_SPACE, vbNullString
        Case 1
            SendMessage hWnd, WM_LBUTTONDOWN, 0&, 0&
        Case 2
            SendMessage hWnd, WM_LBUTTONUP, 0&, 0&
        Case 3
            SendMessage hWnd, WM_LBUTTONDBLCLK, 0&, 0&
        Case 4
            SendMessage hWnd, WM_RBUTTONDOWN, 0&, 0&
        Case 5
            SendMessage hWnd, WM_RBUTTONUP, 0&, 0&
        Case 6
            SendMessage hWnd, WM_RBUTTONDBLCLK, 0&, 0&
    End Select
End Sub
Public Function GetWindowInfo() As WINDOW_INFO
Dim CursorPos As POINTAPI
Dim hProcess As Long
    GetCursorPos CursorPos
    With GetWindowInfo
        .hWnd = WindowFromPoint(CursorPos.X, CursorPos.Y)
        .Parent_hWnd = GetParent(.hWnd)
        .WindowCaption = GetCaption(.hWnd)
        If GetWindowThreadProcessId(.hWnd, hProcess) Then .EXEPath = GetProcessFilename(hProcess)
        GetClassName .hWnd, .ClassName, Len(.ClassName)
        .hInstance = GetWindowLong(.hWnd, GWL_HINSTANCE)
        If .hInstance Then
            If GetModuleFileName(.hInstance, .ModuleFilename, Len(.ModuleFilename)) = 0 Then
                .ModuleFilename = ""
            ElseIf InStr(.ModuleFilename, Chr(0)) Then
                .ModuleFilename = Left(.ModuleFilename, InStr(.ModuleFilename, Chr(0)) - 1)
            End If
        End If
        GetWindowRect .hWnd, .WindowRECT
        If IsIconic(.hWnd) Then
            .WindowState = 1
            Else
            .WindowState = 0
        End If
        If IsZoomed(.hWnd) Then
            .WindowState = 2
            Else
            .WindowState = 0
        End If
        .WindowEnabled = IsWindowEnabled(.hWnd)
    End With
End Function

Public Function CloseWindow(ByVal hWnd As Long) As Long
    CloseWindow = PostMessage(hWnd, WM_CLOSE, 0&, 0&)
End Function

Download WindowMod.bas

Back to file list


Back to project page