Projects

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

Window Spy

Browsing EnumerationMod.bas (5.40 KB)

Attribute VB_Name = "EnumerationMod"
Option Explicit

Private Type MENUITEMINFO
    cbSize As Long
    fMask As Long
    fType As Long
    fState As Long
    wID As Long
    hSubMenu As Long
    hbmpChecked As Long
    hbmpUnchecked As Long
    dwItemData As Long
    dwTypeData As String
    cch As Long
End Type

Private Declare Function EnumChildWindows Lib "user32" (ByVal hwndParent As Long, ByVal lpEnumFunc As Long, ByVal lParam As Any) As Long
Private Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Any) 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 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 CheckMenuItem Lib "user32" (ByVal hMenu As Long, ByVal wIDCheckItem As Long, ByVal wCheck As Long) As Long
Private Declare Function GetMenu Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function GetMenuItemCount Lib "user32" (ByVal hMenu As Long) As Long
Private Declare Function GetMenuItemID Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long
Private Declare Function GetMenuItemInfo Lib "user32" Alias "GetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal b As Long, lpMenuItemInfo As MENUITEMINFO) As Long
Private Declare Function GetSubMenu Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long

Public Declare Function EnableMenuItem Lib "user32" (ByVal hMenu As Long, ByVal wIDEnableItem As Long, ByVal wEnable As Long) As Long
Public Declare Function GetMenuState Lib "user32" (ByVal hMenu As Long, ByVal wID As Long, ByVal wFlags As Long) As Long
Public Declare Function ModifyMenu Lib "user32" Alias "ModifyMenuA" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpString As Any) As Long

Private Const MIIM_TYPE = &H10
Private Const MFT_STRING = &H0&

Public Sub StartChildWinEnum(ByVal hWnd As Long, ListViewObj As Object)
    EnumChildWindows hWnd, AddressOf EnumChildWindowsProc, ListViewObj
End Sub

Public Function EnumWindowsProc(ByVal hWnd As Long, ByVal lParam As ListView) As Long
    Dim WClass As String * 100
    Dim WText As String
    Dim WTextLen As Long
    GetClassName hWnd, WClass, 50
    WText = GetCaption(hWnd, WTextLen)
    With EnumWindowsForm
        If .Check1.Value = 0 Then
            EnumWindowsForm.AddListViewItem lParam, "&H" & Hex(hWnd), WClass, WText
        ElseIf (.Check1.Value = 1 And WTextLen <> 0) Then
            EnumWindowsForm.AddListViewItem lParam, "&H" & Hex(hWnd), WClass, WText
        End If
    End With
    EnumWindowsProc = 1
End Function
Public Function EnumChildWindowsProc(ByVal hWnd As Long, ByVal lParam As ListView) As Long
    Dim ClassName As String * 100
    GetClassName hWnd, ClassName, Len(ClassName)
    EnumWindowsForm.AddListViewItem lParam, "&H" & Hex(hWnd), ClassName, GetCaption(hWnd)
    'lParam.Sorted = True
    EnumChildWindowsProc = 1
End Function


Public Function MenuExists(ByVal hWnd As Long) As Long
    MenuExists = GetMenu(hWnd)
End Function


Public Sub MenuSpy_BuildTree(hMenu As Long, TreeViewObj As TreeView, Optional tmpKey As String, Optional iSubFlag As Boolean)
    Static iKey As Integer
    Dim n As Long, c As Long, i As Long
    Dim MenuID As Long
    Dim iNode As Object
    Dim menusX As MENUITEMINFO
    Dim temp As String
    On Error Resume Next
    
    n = GetMenuItemCount(hMenu)
    For i = 0 To n - 1
        c = GetMenuItemID(hMenu, i)
        MenuID = c
        menusX.cbSize = Len(menusX)
        menusX.fMask = MIIM_TYPE
        menusX.fType = MFT_STRING
        menusX.dwTypeData = Space(255)
        menusX.cch = 255
        GetMenuItemInfo hMenu, i, True, menusX
        menusX.dwTypeData = Trim(menusX.dwTypeData)
        
        If (menusX.dwTypeData = "" Or c = -1) Then
            c = iKey
            iKey = iKey + 1
        Else
            c = c + 15000
        End If
        
        If iSubFlag = False Then
            Set iNode = TreeViewObj.Nodes.Add()
            If tmpKey <> "" Then
                iNode.Relative = tmpKey
                iNode.Relationship = tvwNext
            Else
                iNode.Relationship = tvwLast
            End If
            iNode.Text = menusX.dwTypeData
            iNode.Tag = CStr(hMenu) + "|" + CStr(MenuID)
            If GetSubMenu(hMenu, i) > 1 Then
                iSubFlag = True
                iNode.Key = "k" & CStr(c)
                tmpKey = iNode.Key
                MenuSpy_BuildTree GetSubMenu(hMenu, i), TreeViewObj, tmpKey, True
                iSubFlag = False
            End If
        Else
            Set iNode = TreeViewObj.Nodes.Add(tmpKey, tvwChild, "k" & CStr(c), menusX.dwTypeData)
            iNode.Tag = CStr(hMenu) + "|" + CStr(MenuID)
            If GetSubMenu(hMenu, i) > 1 Then
                iSubFlag = True
                iNode.Key = "k" & CStr(c)
                temp = tmpKey
                tmpKey = iNode.Key
                MenuSpy_BuildTree GetSubMenu(hMenu, i), TreeViewObj, tmpKey, True
                tmpKey = temp
            End If
        End If
    Next i
End Sub
Public Sub StartWinEnum(ListViewObj As Object)
    EnumWindows AddressOf EnumWindowsProc, ListViewObj
End Sub


Download EnumerationMod.bas

Back to file list


Back to project page