GetUserFormHandle

Unlike Visual Basic, VBA UserForms do not have the HWnd property that gives access to the form's window handle. The window handle is required when using the window-related Windows API. The following routine allows you to get VBA UserForms window handle. The technique used is quite simple: Set the UserForm's caption to a unique string (we use a GUID for the unique string), find the window's handle using the FindWindow() API and finally reset the UserForm's caption back to what it was. You can call this GetUserFormHandle() function even from the UserForm's Initialize event.

Private Type GUID
    Data1 As Long
    Data2 As Integer
    Data3 As Integer
    Data4(7) As Byte
End Type

Private Declare Function CoCreateGuid Lib "ole32.dll" (G As GUID) As Long
Private Declare Function StringFromGUID2 Lib "ole32.dll" (G As GUID, _
    ByVal str As String, _
    ByVal cchMax As Long) As Long

Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" ( _
    ByVal lpClassName As String, _
    ByVal lpWindowName As String) As Long

Private Function GetGUID() As String
    Dim G As GUID
    Dim S As String

    S = String(76, vbNullChar)
    CoCreateGuid G
    StringFromGUID2 G, S, Len(S)
    S = StrConv(S, vbFromUnicode)
    GetGUID = S
End Function

Private Function GetUserFormHandle(ByVal UF As Object)
    Dim S As String
    Dim OrigCaption As String

    S = GetGUID()
    OrigCaption = UF.Caption
    UF.Caption = S
    GetUserFormHandle = FindWindow(vbNullString, S)
    UF.Caption = OrigCaption
End Function

Private Sub UserForm_Initialize()
    MsgBox "UserForm window handle: 0x" + Hex(GetUserFormHandle(Me))
End Sub

Contact OfficeOne on email at officeone@officeoneonline.com. Copyright © 2001-2023 OfficeOne. All rights reserved.