Userform ohne Titelleiste

30.05.2002


Über einige API-Aufrufe ist es möglich,
die Titelleiste einer Userform zu verstecken.
Private Declare Function FindWindow Lib "user32" Alias _
      "FindWindowA" (ByVal lpClassName As String, ByVal _
      lpWindowName As String) As Long
Private Declare Function GetWindowLong Lib "user32" Alias _
      "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex _
      As Long) As Long
Private Declare Function SetWindowLong Lib "user32" Alias _
      "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex _
      As Long, ByVal dwNewLong As Long) As Long
Private Declare Function DrawMenuBar Lib "user32" (ByVal _
      hwnd 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 ReleaseCapture Lib "user32" () As Long
Private wHandle As Long
Private Sub UserForm_Initialize()
    If Val(Application.Version) >= 9 Then
        wHandle = FindWindow("ThunderDFrame", Me.Caption)
    Else
        wHandle = FindWindow("ThunderXFrame", Me.Caption)
    End If
    If wHandle = 0 Then Exit Sub
    frm = GetWindowLong(wHandle, GWL_STYLE)
    frm = frm Or &HC00000
    SetWindowLong wHandle, -16, frmStyle
    DrawMenuBar wHandle
End Sub
Private Sub UserForm_MouseDown(ByVal Button As Integer, ByVal _
        Shift As Integer, ByVal X As Single, ByVal Y As Single)
    If wHandle = 0 Then Exit Sub
    If Button = 1 Then
        ReleaseCapture
        SendMessage wHandle, &HA1, 2, 0
    End If
End Sub
Beispieldatei - 9 KB