'==========================
' Module: WindowIdentifier
' Purpose: Identify external app windows without relying on PID
'==========================
Option Compare Database
Option Explicit
' Windows API declarations
Private Declare PtrSafe Function EnumWindows Lib "user32" _
    (ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Long
Private Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" _
    (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long
Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" _
    (ByVal hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Private Declare PtrSafe Function GetWindowThreadProcessId Lib "user32" _
    (ByVal hwnd As LongPtr, lpdwProcessId As Long) As Long
' Store matched windows
Public MatchedWindows As Collection
' Entry point: call this to find windows by title or class
Public Sub FindWindowsByPattern(ByVal titlePattern As String, ByVal classPattern As String)
    Set MatchedWindows = New Collection
    EnumWindows AddressOf EnumWindowsProc, ByVal 0
    Debug.Print "Found " & MatchedWindows.Count & " matching windows."
End Sub
' Callback for EnumWindows
Private Function EnumWindowsProc(ByVal hwnd As LongPtr, ByVal lParam As LongPtr) As Long
    Dim winTitle As String, winClass As String
    winTitle = GetWindowTitle(hwnd)
    winClass = GetWindowClass(hwnd)
    ' Match patterns (case-insensitive)
    If (titlePattern <> "" And InStr(1, winTitle, titlePattern, vbTextCompare) > 0) Or _
       (classPattern <> "" And InStr(1, winClass, classPattern, vbTextCompare) > 0) Then
        MatchedWindows.Add hwnd
        Debug.Print "Match: hWnd=" & hwnd & " | Title=" & winTitle & " | Class=" & winClass
    End If
    EnumWindowsProc = 1 ' Continue enumeration
End Function
' Helpers to get window title and class
Private Function GetWindowTitle(ByVal hwnd As LongPtr) As String
    Dim buffer As String * 256
    Dim length As Long
    length = GetWindowText(hwnd, buffer, Len(buffer))
    If length > 0 Then GetWindowTitle = Left$(buffer, length)
End Function
Private Function GetWindowClass(ByVal hwnd As LongPtr) As String
    Dim buffer As String * 256
    Dim length As Long
    length = GetClassName(hwnd, buffer, Len(buffer))
    If length > 0 Then GetWindowClass = Left$(buffer, length)
End Function