' 撰寫人:Devil(璉璉) E-Mail: qvb3377@ms5.hinet.net 僅供學術測試使用,引用請註明原出處 ' -------------------------------------------------------------------------------------- ' 視窗 Public Declare Function CloseWindow Lib "user32" (ByVal hWnd As Long) As Long ' 最小化 Public Declare Function DestroyWindow Lib "user32" (ByVal hWnd As Long) As Long ' 關閉視窗 Public Declare Function EnableWindow Lib "user32" (ByVal hWnd As Long, ByVal fEnable As Long) As Long Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long Public Declare Function GetActiveWindow Lib "user32" () As Long Public Declare Function GetDesktopWindow Lib "user32" () As Long Public Declare Function GetForegroundWindow Lib "user32" () As Long Public Declare Function GetWindow Lib "user32" (ByVal hWnd As Long, ByVal wCmd As enuGetWindow) As Long Public Declare Function GetWindowDC Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As enuWindowLong) As Long Public Declare Function GetTopWindow Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function IsWindow Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function IsWindowUnicode Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function IsWindowVisible Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function Win32SetFocus Lib "user32" Alias "SetFocus" (ByVal hWnd As Long) As Long Public Declare Function SetActiveWindow Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function SetForegroundWindow Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long Public 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 enuSetWindowPos) As Long Public Declare Function ShowWindow Lib "user32" (ByVal hWnd As Long, ByVal nCmdShow As Integer) As Long Public Declare Function UpdateWindow Lib "user32" (ByVal hWnd As Long) As Long Private Declare Function MessageBoxTimeout Lib "user32" Alias "MessageBoxTimeoutA" (ByVal hWnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal uType As Long, ByVal wLanguageId As Long, ByVal dwMilliseconds As Long) As Long Private Declare Function SendMessageByNum Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long ' 從點座標取得 hWnd Public Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long Public Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long Private Type POINTAPI X As Long Y As Long End Type ' 從滑鼠位置取得 hWnd Public Declare Function GetCapture Lib "user32" () 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 SetWindowText Lib "user32" Alias "SetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String) As Long ' 視窗模組名稱 Private Declare Function GetWindowModuleFileName Lib "user32" Alias "GetWindowModuleFileNameA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long ' 列舉 Private Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, lParam As Long) As Long Private Declare Function EnumDesktopWindows Lib "user32" (ByVal hDesktop As Long, ByVal lpEnumFunc As Long, lParam As Long) As Long Private Declare Function EnumThreadWindows Lib "user32" (ByVal dwThreadId As Long, ByVal lpEnumFunc As Long, lParam As Long) As Long Private Declare Function EnumChildWindows Lib "user32" (ByVal hWndParent As Long, ByVal lpEnumFunc As Long, lParam As Long) As Long ' 執行緒 'Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, dwProcessId 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 GetClassLong Lib "user32" Alias "GetClassLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long Private Declare Function SetClassLong Lib "user32" Alias "SetClassLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long ' 從屬 Public Declare Function SetParent Lib "user32" (ByVal hWndChild As Long, ByVal hWndNewParent As Long) As Long Public Declare Function GetParent Lib "user32" (ByVal hWnd As Long) As Long ' 視焦 Public Declare Function GetFocus Lib "user32" () As Long Public Declare Function SetFocus Lib "user32" (ByVal hWnd As Long) As Long ' 訊息 Private Declare Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hWnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long Private Declare Function MessageBoxEx Lib "user32" Alias "MessageBoxExA" (ByVal hWnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal uType As Long, ByVal wLanguageId As Long) As Long ' GetClassLong, SetClassLong Private Const GCL_STYLE = (-26) Private Enum enuClassStyles CS_BYTEALIGNCLIENT = &H1000 CS_BYTEALIGNWINDOW = &H2000 CS_CLASSDC = &H40 CS_DBLCLKS = &H8 CS_HREDRAW = &H2 CS_INSERTCHAR = &H2000 CS_KEYCVTWINDOW = &H4 CS_NOCLOSE = &H200 CS_NOKEYCVT = &H100 CS_NOMOVECARET = &H4000 CS_OWNDC = &H20 CS_PARENTDC = &H80 CS_PUBLICCLASS = &H4000 CS_SAVEBITS = &H800 CS_VREDRAW = &H1 End Enum ' GetWindow Public Enum enuGetWindow GW_CHILD = 5 GW_HWNDFIRST = 0 GW_HWNDLAST = 1 GW_HWNDNEXT = 2 GW_HWNDPREV = 3 GW_MAX = 5 GW_OWNER = 4 End Enum ' SetWindowLong Public Enum enuWindowStyles WS_BORDER = &H800000 WS_CAPTION = &HC00000 ' WS_BORDER Or WS_DLGFRAME WS_CHILD = &H40000000 WS_CHILDWINDOW = (WS_CHILD) WS_CLIPCHILDREN = &H2000000 WS_CLIPSIBLINGS = &H4000000 WS_DISABLED = &H8000000 WS_DLGFRAME = &H400000 WS_EX_ACCEPTFILES = &H10& WS_EX_DLGMODALFRAME = &H1& WS_EX_NOPARENTNOTIFY = &H4& WS_EX_TOPMOST = &H8& WS_EX_TRANSPARENT = &H20& WS_GROUP = &H20000 WS_HSCROLL = &H100000 WS_MAXIMIZE = &H1000000 WS_MAXIMIZEBOX = &H10000 WS_MINIMIZE = &H20000000 WS_ICONIC = WS_MINIMIZE WS_MINIMIZEBOX = &H20000 WS_OVERLAPPED = &H0& WS_POPUP = &H80000000 WS_SYSMENU = &H80000 WS_TABSTOP = &H10000 WS_THICKFRAME = &H40000 WS_TILED = WS_OVERLAPPED WS_VISIBLE = &H10000000 WS_VSCROLL = &H200000 WS_SIZEBOX = WS_THICKFRAME WS_OVERLAPPEDWINDOW = (WS_OVERLAPPED Or WS_CAPTION Or WS_SYSMENU Or WS_THICKFRAME Or WS_MINIMIZEBOX Or WS_MAXIMIZEBOX) WS_POPUPWINDOW = (WS_POPUP Or WS_BORDER Or WS_SYSMENU) WS_TILEDWINDOW = WS_OVERLAPPEDWINDOW End Enum ' GetWindowLong Public Enum enuWindowLong GWL_EXSTYLE = -20 GWL_HINSTANCE = -6 GWL_HWNDPARENT = -8 GWL_ID = -12 GWL_STYLE = -16 GWL_USERDATA = -21 GWL_WNDPROC = -4 End Enum ' ShowWindow API Public Enum enuShowWindow SW_HIDE = 0 SW_SHOWNORMAL = 1 SW_NORMAL = 1 SW_SHOWMINIMIZED = 2 SW_SHOWMAXIMIZED = 3 SW_MAXIMIZE = 3 SW_SHOWNOACTIVATE = 4 SW_SHOW = 5 SW_MINIMIZE = 6 SW_SHOWMINNOACTIVE = 7 SW_SHOWNA = 8 SW_RESTORE = 9 SW_SHOWDEFAULT = 10 SW_FORCEMINIMIZE = 11 SW_MAX = 11 End Enum ' SetWindowPos Private Enum enuInsertAfter hWnd_NoTopMost = -2 hWnd_TopMost = -1 hWnd_Bottom = 1 hWnd_BROADCAST = &HFFFF& hWnd_Desktop = 0 hWnd_Top = 0 End Enum ' tFlags = SWP_NOSize Or SWP_NOMove Or SWP_NOActivate Or SWP_ShowWindow Public Enum enuSetWindowPos SWP_NOSIZE = &H1 SWP_NOMOVE = &H2 SWP_NOZORDER = &H4 SWP_NOREDRAW = &H8 SWP_NOACTIVATE = &H10 SWP_FRAMECHANGED = &H20 ' The frame changed: send WM_NCCALCSIZE SWP_SHOWWINDOW = &H40 SWP_HIDEWINDOW = &H80 SWP_NOCOPYBITS = &H100 SWP_NOOWNERZORDER = &H200 SWP_NOSENDCHANGING = &H400 SWP_DEFERERASE = &H2000 SWP_ASYNCWINDOWPOS = &H4000 SWP_DRAWFRAME = SWP_FRAMECHANGED SWP_NOREPOSITION = SWP_NOOWNERZORDER SWP_Default = SWP_NOSIZE Or SWP_NOMOVE Or SWP_NOACTIVATE Or SWP_SHOWWINDOW End Enum Public Enum enuEnumWindows enu_EW_hWnd = 0 enu_EW_Text = 1 enu_EW_Class = 2 enu_EW_ModuleFileName = 3 enu_EW_OnlyVisible = &H100 enu_EW_OnlyParentWindow = &H200 enu_EW_OnlyAppication = &H400 End Enum ' 自訂 Public Enum enuMyhWnd MyhWnd_Default = 0 MyhWnd_Active = 1 MyhWnd_Foreground = 2 MyhWnd_Focus = 3 MyhWnd_Top = 4 End Enum Public Enum WindowMessages WM_NULL = &H0 WM_CREATE = &H1 WM_DESTROY = &H2 WM_MOVE = &H3 WM_SIZE = &H5 WM_ACTIVATE = &H6 WM_SETFOCUS = &H7 WM_KILLFOCUS = &H8 WM_ENABLE = &HA WM_SETREDRAW = &HB WM_SETTEXT = &HC WM_GETTEXT = &HD WM_GETTEXTLENGTH = &HE WM_PAINT = &HF WM_Close = &H10 WM_QUERYENDSESSION = &H11 WM_QUERYOPEN = &H13 WM_ENDSESSION = &H16 WM_QUIT = &H12 WM_ERASEBKGND = &H14 WM_SYSCOLORCHANGE = &H15 WM_SHOWWINDOW = &H18 WM_WININICHANGE = &H1A WM_SETTINGCHANGE = WM_WININICHANGE WM_DEVMODECHANGE = &H1B WM_ACTIVATEAPP = &H1C WM_FONTCHANGE = &H1D WM_TIMECHANGE = &H1E WM_CANCELMODE = &H1F WM_SETCURSOR = &H20 WM_MOUSEACTIVATE = &H21 WM_CHILDACTIVATE = &H22 WM_QUEUESYNC = &H23 WM_GETMINMAXINFO = &H24 WM_SYSCOMMAND = &H112& WM_CTLCOLORMSGBOX = &H132 WM_CTLCOLOREDIT = &H133 WM_CTLCOLORLISTBOX = &H134 WM_CTLCOLORBTN = &H135 WM_CTLCOLORDLG = &H136 WM_CTLCOLORSCROLLBAR = &H137 WM_CTLCOLORSTATIC = &H138 MN_GETHMENU = &H1E1 WM_MOUSEFIRST = &H200 WM_MOUSEMOVE = &H200 WM_LBUTTONDOWN = &H201 WM_LBUTTONUP = &H202 WM_LBUTTONDBLCLK = &H203 WM_RBUTTONDOWN = &H204 WM_RBUTTONUP = &H205 WM_RBUTTONDBLCLK = &H206 WM_MBUTTONDOWN = &H207 WM_MBUTTONUP = &H208 WM_MBUTTONDBLCLK = &H209 WM_MOUSEWHEEL = &H20A WM_XBUTTONDOWN = &H20B WM_XBUTTONUP = &H20C WM_XBUTTONDBLCLK = &H20D WM_MOUSEHWHEEL = &H20E WM_MOUSELAST = &H20E ' > WinNT 6 'WM_MOUSELAST = &H20D ' > WinNT 5 'WM_MOUSELAST = &H20A ' > WinNT 4 'WM_MOUSELAST = &H209 ' Else WM_USER = &H400 End Enum Private Enum ControlWindowMessage ' ListBox LB_SETHORIZONTALEXTENT = &H194 End Enum Private Const BufferString = 256 Private enumhWndWindows() As Long Public Function SendCloseWindowMessage(ByVal hWnd As Long) As Boolean Dim rtnValue As Long If hWnd > 0 Then If IsWindowVisible(hWnd) Then rtnValue = SendMessageByNum(hWnd, WM_Close, 0, 0) SendCloseWindowMessage = (rtnValue = 0) End Function Public Function GetListBoxTextWidth(ByVal oForm As Object, ByVal oListBox As ListBox) As Long Dim maxWidth As Long, nowWidth As Long maxWidth = oListBox.Width For i = 0 To oListBox.ListCount - 1 nowWidth = oForm.TextWidth(oListBox.List(i) & " ") If maxWidth < nowWidth Then maxWidth = nowWidth Next GetListBoxTextWidth = maxWidth End Function Public Sub ListBoxAddHScrollBar(ByVal oListBox As ListBox, ByVal twipsWidth As Long) twipsWidth = twipsWidth / Screen.TwipsPerPixelX ' if twips change to pixels SendMessageByNum oListBox.hWnd, LB_SETHORIZONTALEXTENT, twipsWidth, 0 End Sub Public Function MsgBoxTimeout(ByVal Prompt As String, Optional ByVal Buttons As VbMsgBoxStyle = vbOKOnly, Optional ByVal Title As String = "", Optional ByVal dwMilliseconds As Long = 10000, Optional ByVal hWnd As Long = 0) As VbMsgBoxResult If Len(Title) = 0 Then Title = App.Title MsgBoxTimeout = MessageBoxTimeout(hWnd, Prompt, Title, Buttons, 1, dwMilliseconds) End Function Public Function myGetCursorWindow() As Long Dim tPoint As POINTAPI summy = GetCursorPos(tPoint) myGetCursorWindow = WindowFromPoint(tPoint.X, tPoint.Y) End Function Public Function myIsWindowUnicode(ByVal hWnd As Long) As Boolean myIsWindowUnicode = IsWindowUnicode(hWnd) End Function Function myGetInstance(ByVal hWnd As Long) As Long myGetInstance = GetWindowLong(hWnd, GWL_HINSTANCE) End Function Public Function myGetWindowModuleFileName(ByVal hWnd As Long) As String Dim lpString As String lpString = String(BufferString, 0) GetWindowModuleFileName hWnd, lpString, BufferString myGetWindowModuleFileName = Left(lpString, InStr(lpString, Chr(0)) - 1) End Function Public Function myAppActivate(ByVal hString As String) hWnd = FindWindowTitle(hString) SetActiveWindow hWnd SetFocus hWnd 'EnableWindow hWnd, True 'ShowWindow hWnd, SW_SHOWNA End Function Public Function myAddressOf(ByVal hAddress As Long) As Long myAddressOf = hAddress End Function Private Function EnumWindowsProc(ByVal hWnd As Long, lParam As Long) As Long lParam = lParam + 1 ReDim Preserve enumhWndWindows(1 To lParam) As Long enumhWndWindows(lParam) = hWnd ' Return True to keep enumerating EnumWindowsProc = True End Function Private Function FilterEnumWindows(ByVal enumType As enuEnumWindows) Dim enumWindowsType() Dim tWnd() As Long, nCount As Long On Error Resume Next lb = LBound(enumhWndWindows) tErrN = Err.Number On Error GoTo 0 If tErrN > 0 Then ReDim enumWindowsType(1 To 1) Else lb = LBound(enumhWndWindows) ub = UBound(enumhWndWindows) For i = lb To ub swText = enumhWndWindows(i) If enu_EW_OnlyVisible And enumType And IsWindowVisible(enumhWndWindows(i)) Then swText = Empty End If If enu_EW_OnlyParentWindow And enumType Then If GetParent(enumhWndWindows(i)) <> 0 Then swText = Empty End If End If If swText <> Empty Then nCount = nCount + 1 ReDim Preserve tWnd(1 To nCount) As Long tWnd(nCount) = swText End If Next i lb = LBound(tWnd) ub = UBound(tWnd) tType = enumType Mod &H100 nCount = 0 For i = lb To ub Select Case tType Case Is = enu_EW_hWnd swText = tWnd(i) Case Is = enu_EW_Text swText = myGetWindowText(tWnd(i)) Case Is = enu_EW_Class swText = myGetClassName(tWnd(i)) Case Is = enu_EW_ModuleFileName swText = myGetWindowModuleFileName(tWnd(i)) End Select If swText <> Empty Then nCount = nCount + 1 ReDim Preserve enumWindowsType(1 To nCount) enumWindowsType(nCount) = swText End If Next i End If FilterEnumWindows = enumWindowsType End Function Public Function myEnumChildWindows(ByVal hWndParent As Long, Optional ByVal enumType As enuEnumWindows = enu_EW_hWnd) Erase enumhWndWindows summy = EnumChildWindows(hWndParent, AddressOf EnumWindowsProc, lParam) myEnumChildWindows = FilterEnumWindows(enumType) Erase enumhWndWindows End Function Public Function myEnumWindows(Optional ByVal enumType As enuEnumWindows = enu_EW_hWnd) Erase enumhWndWindows summy = EnumWindows(AddressOf EnumWindowsProc, lParam) myEnumWindows = FilterEnumWindows(enumType) Erase enumhWndWindows End Function Function myEnumDesktopWindows(ByVal hDesktop As Long, Optional ByVal enumType As enuEnumWindows = enu_EW_hWnd) Erase enumhWndWindows summy = EnumDesktopWindows(hDesktop, AddressOf EnumWindowsProc, c) myEnumDesktopWindows = FilterEnumWindows(enumType) Erase enumhWndWindows 'On Error Resume Next ' 'lb = LBound(enumhWndWindows) 'tErrN = Err.Number ' 'On Error GoTo 0 ' 'If tErrN > 0 Then ' ReDim enumWindowsText(1 To 1) As String 'Else ' lb = LBound(enumhWndWindows) ' ub = UBound(enumhWndWindows) ' ' nCount = 0 ' For i = lb To ub ' swText = myGetWindowText(enumhWndWindows(i)) ' If swText <> "" Then ' nCount = nCount + 1 ' ReDim Preserve enumWindowsText(1 To nCount) As String ' ' enumWindowsText(nCount) = swText ' End If ' Next i 'End If ' 'myEnumDesktopWindows = enumWindowsText End Function Function myEnumThreadWindows(ByVal dwThreadId As Long) Erase enumhWndWindows f = EnumThreadWindows(dwThreadId, AddressOf EnumWindowsProc, c) myEnumThreadWindows = enumhWndWindows End Function Public Function myHWnd(Optional ByVal dwFlags As enuMyhWnd = MyhWnd_Default) As Long Select Case dwFlags Case MyhWnd_Default hWnd = FindWindowTitle(App.Title) Case MyhWnd_Active hWnd = GetActiveWindow Case Is = MyhWnd_Foreground hWnd = GetForegroundWindow Case MyhWnd_Focus hWnd = GetFocus Case MyhWnd_Top hWnd = GetTopWindow(0) End Select If dwFlags = MyhWnd_Default And hWnd = 0 Then hWnd = GetActiveWindow If hWnd = 0 Then hWnd = GetForegroundWindow End If End If myHWnd = hWnd End Function Public Function Win32MsgBox(ByVal lpText As String, Optional ByVal wType As VbMsgBoxStyle = vbOKOnly, Optional ByVal lpCaption As String, Optional ByVal hWnd As Long = 0) If lpCaption = "" Then lpCaption = App.Title End If If hWnd = 0 Then hWnd = myHWnd End If Win32MsgBox = MessageBox(hWnd, lpText, lpCaption, wType) End Function Public Function FindWindowClass(ByVal lpClassName As String) As Long FindWindowClass = FindWindow(lpClassName, vbNullString) End Function Public Function FindWindowTitle(ByVal lpWindowName As String) As Long FindWindowTitle = FindWindow(vbNullString, lpWindowName) End Function Public Function SetAlwaysOnTop(ByVal hWnd As Long, Optional ByVal wFlags As enuSetWindowPos = SWP_Default, Optional ByVal OnTop As Boolean = True) If OnTop Then hWndInsertAfter = hWnd_TopMost Else hWndInsertAfter = hWnd_NoTopMost End If SetWindowPos hWnd, hWndInsertAfter, 0, 0, 0, 0, wFlags End Function Public Function CancelAlwaysOnTop(ByVal hWnd As Long, Optional ByVal wFlags As enuSetWindowPos = SWP_Default) SetWindowPos hWnd, hWnd_NoTopMost, 0, 0, 0, 0, wFlags End Function Public Function SetCaptionBoxDisable(ByVal hWnd As Long, Optional ByVal MaxSizeBox As Boolean = True, Optional ByVal MinSizeBox As Boolean = True) ' 用 VB 的 Me.MaxButton, Me.MinButton 較好 Dim thWnd As Long thWnd = GetWindowLong(hWnd, GWL_STYLE) If MaxSizeBox Then thWnd = thWnd Or (WS_MAXIMIZEBOX) Else thWnd = thWnd And Not (WS_MAXIMIZEBOX) End If If MinSizeBox Then thWnd = thWnd Or (WS_MINIMIZEBOX) Else thWnd = thWnd And Not (WS_MINIMIZEBOX) End If thWnd = SetWindowLong(hWnd, GWL_STYLE, thWnd) ShowWindow hWnd, SW_HIDE ShowWindow hWnd, SW_SHOWNORMAL SetCaptionBoxDisable = thWnd End Function Public Function CheckWindowStyles(ByVal hWnd As Long, ByVal hWindowStyles As enuWindowStyles) As Boolean tWindowStyles = GetWindowLong(hWnd, GWL_STYLE) If tWindowStyles And hWindowStyles Then CheckWindowStyles = True Else CheckWindowStyles = False End If End Function Public Function AppOwnerWindowNoMinimize(ByVal hWnd As Long) tWnd = GetWindow(hWnd, GW_OWNER) tWindowStyles = GetWindowLong(tWnd, GWL_STYLE) AppOwnerWindowNoMinimize = tWindowStyles tWindowStyles = tWindowStyles And (Not WS_MINIMIZE) SetWindowLong tWnd, GWL_STYLE, tWindowStyles End Function Private Function myClassStyles(ByVal hWnd As Long) tClassStyles = GetClassLong(hWnd, GCL_STYLE) myClassStyles = tClassStyles tClassStyles = tClassStyles Or CS_NOCLOSE SetClassLong hWnd, GCL_STYLE, tClassStyles End Function Public Function myGetClassName(ByVal hWnd As Long) As String Dim lpString As String lpString = String(BufferString, 0) GetClassName hWnd, lpString, BufferString myGetClassName = Left(lpString, InStr(lpString, Chr(0) & Chr(0)) - 1) End Function Public Function myGetWindowText(ByVal hWnd As Long) As String TextBuffer = GetWindowTextLength(hWnd) + 1 Dim lpString As String lpString = String(TextBuffer, 0) GetWindowText hWnd, lpString, TextBuffer myGetWindowText = Left(lpString, Len(lpString) - 1) End Function