Generic MouseWheel Scroll for UserForm and for ALL its Controls !

Jaafar Tribak

Well-known Member
Joined
Dec 5, 2002
Messages
9,621
Office Version
  1. 2016
Platform
  1. Windows
Hi all,
Below is a code for scrolling all controls in a userform with the Mouse Wheel

Should work with Modal as well as with Modeless userforms .. Tested in 32Bit and 64Bit systems .. Also, the code doesn't use a Windows hook so it should be stable and safe.

See Workbook Demo

1- Code in a Standard Module :
Code:
Option Explicit

Public Enum CTRL_KEY_PRESS_STATE
    Released
    Pressed
End Enum

Public Enum WHEEL_ROTATION
    Forward
    Backward
End Enum

Private Type POINTAPI
  X As Long
  Y As Long
End Type

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

Private Type LongToInteger
    Low As Integer
    High As Integer
End Type

#If VBA7 Then
    Private Type MSG
        hwnd As LongPtr
        message As Long
        wParam As LongPtr
        lParam As LongPtr
        time As Long
        pt As POINTAPI
    End Type
    
    Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
    Private Declare PtrSafe Function GetDeviceCaps Lib "gdi32" (ByVal hdc As LongPtr, ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function GetDC Lib "user32" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hdc As LongPtr) As Long
    Private Declare PtrSafe Function ClientToScreen Lib "user32" (ByVal hwnd As LongPtr, lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Function GetParent Lib "user32" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongPtr) As LongPtr
    Private Declare PtrSafe Function GetNextWindow Lib "user32" Alias "GetWindow" (ByVal hwnd As LongPtr, ByVal wFlag As Long) As LongPtr
    Private Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function PeekMessage Lib "user32" Alias "PeekMessageA" (lpMsg As MSG, ByVal hwnd As LongPtr, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long, ByVal wRemoveMsg As Long) As Long
    Private Declare PtrSafe Function WaitMessage Lib "user32" () 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 GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Sub ZeroMemory Lib "kernel32" Alias "RtlZeroMemory" (dest As Any, ByVal numBytes As LongPtr)
    Private Declare PtrSafe Function IsBadCodePtr Lib "kernel32" (ByVal lpfn As LongPtr) As Long
#If Win64 Then
     Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongPtr, ppacc As Any, pvarChild As Variant) As Long
#Else
     Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
#End If

#Else
    Private Type MSG
        hwnd As Long
        message As Long
        wParam As Long
        lParam As Long
        time As Long
        pt As POINTAPI
    End Type
    Private Declare Function GetDeviceCaps Lib "gdi32" (ByVal hdc As Long, ByVal nIndex As Long) As Long
    Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function GetParent Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
    Private Declare Function GetNextWindow Lib "user32" Alias "GetWindow" (ByVal hwnd As Long, ByVal wCmd 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 GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
    Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
    Private Declare Function ClientToScreen Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
    Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As Long
    Private Declare Function WaitMessage Lib "user32" () As Long
    Private Declare Function PeekMessage Lib "user32" Alias "PeekMessageA" (lpMsg As MSG, ByVal hwnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long, ByVal wRemoveMsg As Long) As Long
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
    Private Declare Function AccessibleObjectFromPoint Lib "Oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Sub ZeroMemory Lib "kernel32.dll" Alias "RtlZeroMemory" (Destination As Any, ByVal Length As Long)
    Private Declare Function IsBadCodePtr Lib "kernel32" (ByVal lpfn As Long) As Long
#End If
 
Private Const CHILDID_SELF = &H0&
Private Const S_OK As Long = &H0
Private Const POINTSPERINCH As Long = 72
Private Const LOGPIXELSX As Long = 88
Private Const LOGPIXELSY As Long = 90
Private Const WM_MOUSEWHEEL = &H20A
Private Const PM_REMOVE = &H1
Private bCancelProcessing As Boolean
Private Const MK_CONTROL = &H8
Private Const SCROLL_CHANGE = 10

Private arObjCaptions() As Variant
Private arObjPointers() As Variant

Public Sub HookMouseWheelScroll(ByVal UF As Object)
    Dim WheelRotation As WHEEL_ROTATION
    Dim CtrlKey As CTRL_KEY_PRESS_STATE
    Dim tMsg As MSG
    Dim tCurPos As POINTAPI
    Dim oIA As IAccessible
    Dim oObjUnderMouse As Object
    Dim oPage As Object
    Dim oCtrl As Object
    Dim vKid  As Variant
    Dim i As Long
    Dim j As Long
    Dim lResult As Long
    Dim bCancel As Boolean
    Static k As Long
    #If VBA7 Then
        Dim Ptr As LongPtr
    #Else
        Dim Ptr As Long
    #End If
    
    bCancelProcessing = False
    k = 0
    UF.Caption = UF.Caption & Chr(10)
    j = 0
    Erase arObjCaptions
    Erase arObjPointers
    For Each oCtrl In UF.Controls
        If TypeName(oCtrl) = "MultiPage" Then
            For Each oPage In oCtrl.Pages
                i = i + 1
                oPage.Caption = oPage.Caption & String(i, Chr(10))
                ReDim Preserve arObjCaptions(j)
                ReDim Preserve arObjPointers(j)
                arObjCaptions(j) = oPage.Caption & Chr(10)
                arObjPointers(j) = ObjPtr(oPage)
                j = j + 1
            Next
        End If
    Next
    Do While Not bCancelProcessing
        DoEvents
        GetCursorPos tCurPos
        #If Win64 Then
            CopyMemory Ptr, tCurPos, LenB(tCurPos)
            lResult = AccessibleObjectFromPoint(Ptr, oIA, vKid)
        #Else
            lResult = AccessibleObjectFromPoint(tCurPos.X, tCurPos.Y, oIA, vKid)
        #End If
        If lResult = S_OK Then
            On Error Resume Next
            Set oObjUnderMouse = objUnderMouse(UF, oIA, tCurPos)
            If Not oObjUnderMouse Is Nothing Then
                WaitMessage
                If PeekMessage(tMsg, 0, WM_MOUSEWHEEL, WM_MOUSEWHEEL, PM_REMOVE) Then
                    CtrlKey = IIf(LoWord(CLng(tMsg.wParam)) = MK_CONTROL, Pressed, Released)
                    WheelRotation = IIf(tMsg.wParam > 0, Forward, Backward)
                    Call UF.OnScrollEvent(oObjUnderMouse, WheelRotation, CtrlKey, tMsg.pt.X, tMsg.pt.Y, bCancel)
                    If Not bCancel Then
                        If TypeName(oObjUnderMouse) = "TextBox" Then
                            With oObjUnderMouse
                                .SetFocus
                                If k = 0 Then
                                    .SelStart = 0
                                Else
                                    .SelStart = IIf(.SelStart = .LineCount, 0, .SelStart)
                                End If
                                If WheelRotation = Forward Then
                                    .CurLine = .CurLine - 1
                                Else
                                    .CurLine = IIf(.CurLine = .LineCount - 1, .CurLine, .CurLine + 1)
                                End If
                            End With
                            k = k + 1
                        End If
                        If TypeName(oObjUnderMouse) = "ScrollBar" Then
                            With oObjUnderMouse
                                If WheelRotation = Forward Then
                                    .Value = IIf(.Value - oObjUnderMouse.SmallChange > .Min, .Value - oObjUnderMouse.SmallChange, .Min)
                                Else
                                    .Value = IIf(.Value + oObjUnderMouse.SmallChange < .Max, .Value + oObjUnderMouse.SmallChange, .Max)
                                End If
                            End With
                        End If
                        If TypeName(oObjUnderMouse) = "ListBox" Or TypeName(oObjUnderMouse) = "ComboBox" Then
                            With oObjUnderMouse
                                If CtrlKey = Released Then
                                    If WheelRotation = Forward Then
                                    .TopIndex = .TopIndex - 1
                                    Else
                                    .TopIndex = .TopIndex + 1
                                    End If
                                Else
                                    .SetFocus
                                    If WheelRotation = Forward Then
                                        SendKeys "{LEFT}", True
                                        DoEvents
                                        SendKeys "{RIGHT}", True
                                    Else
                                        SendKeys "{RIGHT}", True
                                        DoEvents
                                        SendKeys "{RIGHT}", True
                                    End If
                                End If
                            End With
                        End If
                        If TypeName(oObjUnderMouse) = UF.Name Or TypeName(oObjUnderMouse) = "Frame" Or TypeName(oObjUnderMouse) = "Page" Then
                            With oObjUnderMouse
                                If CtrlKey = Released Then
                                    If WheelRotation = Forward Then
                                        .ScrollTop = Application.Max(0, .ScrollTop - 5)
                                    Else
                                        .ScrollTop = Application.Min(.ScrollHeight - .InsideHeight, .ScrollTop + SCROLL_CHANGE)
                                    End If
                                Else
                                    If WheelRotation = Forward Then
                                        .ScrollLeft = Application.Max(0, .ScrollLeft - 5)
                                    Else
                                        .ScrollLeft = Application.Min(.ScrollWidth - .InsideWidth, .ScrollLeft + SCROLL_CHANGE)
                                    End If
                                End If
                            End With
                        End If
                    End If
                    DoEvents
                End If
            End If
        End If
    Loop
End Sub

Public Sub RemoveMouseWheelHook()
    bCancelProcessing = True
End Sub

[B][COLOR=#008000]'Private Routines ..[/COLOR][/B]
[B][COLOR=#008000]'-------------------[/COLOR][/B]
Private Function objUnderMouse(ByVal UF As Object, ByVal oAcc As IAccessible, MouseLoc As POINTAPI) As Object
    #If VBA7 Then
        Dim lngPtr As LongPtr
        Dim lObjPtr As LongPtr
        Dim lCtrlPtr As LongPtr
        Dim hwndForm As LongPtr
        Dim hwndFromPoint As LongPtr
    #Else
        Dim lObjPtr As Long
        Dim lCtrlPtr As Long
        Dim hwndForm As Long
        Dim hwndFromPoint As Long
    #End If
    Dim arCtrlsPosition() As Variant
    Dim arCtrlsPointers() As Variant
    Dim tPt As POINTAPI
    Dim tRect As RECT
    Dim oObj As Object
    Dim oCtrl As Control
    Dim sBuffer As String
    Dim lCtrlLeft As Long
    Dim lCtrlTop As Long
    Dim lPos1 As Long
    Dim lPos2 As Long
    Dim lPos3 As Long
    Dim lRet As Long
    Dim i As Long

    On Error Resume Next
    hwndForm = FindWindow(vbNullString, UF.Caption)
    For Each oCtrl In UF.Controls
        ReDim Preserve arCtrlsPosition(i + 1)
        ReDim Preserve arCtrlsPointers(i + 1)
        tPt = GetRealCtrlScreenLocation(oCtrl, hwndForm, UF)
        arCtrlsPosition(i) = tPt.X & tPt.Y
        arCtrlsPointers(i) = ObjPtr(oCtrl)
        arCtrlsPosition(i + 1) = tPt.X - 2 & tPt.Y - 1
        arCtrlsPointers(i + 1) = ObjPtr(oCtrl)
        i = i + 2
    Next
    lPos1 = WorksheetFunction.Match(oAcc.accName(CHILDID_SELF) & Chr(10), arObjCaptions, 0)
    lObjPtr = WorksheetFunction.Index(arObjPointers, 1, lPos1)
    Call oAcc.accLocation(lCtrlLeft, lCtrlTop, 0, 0, CHILDID_SELF)
    lPos2 = WorksheetFunction.Match(lCtrlLeft & lCtrlTop, arCtrlsPosition, 0)
    lCtrlPtr = WorksheetFunction.Index(arCtrlsPointers, 1, lPos2)
    #If VBA7 Then
        CopyMemory lngPtr, MouseLoc, LenB(MouseLoc)
        hwndFromPoint = WindowFromPoint(lngPtr)
    #Else
        hwndFromPoint = WindowFromPoint(MouseLoc.X, MouseLoc.Y)
    #End If
    sBuffer = Space(256)
    lRet = GetClassName(GetParent(hwndFromPoint), sBuffer, 256)
    lPos3 = InStr(1, Left(sBuffer, lRet), "MdcPopup")
    Select Case True
        Case lPos3 <> 0
            Set objUnderMouse = GetActiveComboBox(UF)
            Exit Function
        Case oAcc.accName(CHILDID_SELF) = UF.Caption
            Set oObj = UF
        Case lObjPtr = 0
            If IsBadCodePtr(lCtrlPtr) = 0 Then
                CopyMemory oObj, lCtrlPtr, 4
            End If
        Case lObjPtr <> 0
            If IsBadCodePtr(lObjPtr) = 0 Then
                CopyMemory oObj, lObjPtr, 4
            End If
    End Select
    Set objUnderMouse = oObj
    If Not oObj Is Nothing Then
        ZeroMemory oObj, 4
    End If
End Function

#If VBA7 Then
    Private Function GetRealCtrlScreenLocation(ByVal Ctl As Object, ByVal hwnd As LongPtr, ByVal UF As Object) As POINTAPI
#Else
    Private Function GetRealCtrlScreenLocation(ByVal Ctl As Object, ByVal hwnd As Long, ByVal UF As Object) As POINTAPI
#End If
    Dim tRect As RECT
    Dim tTopLeft As POINTAPI
    Dim oMultiPage As Control
    Dim oTempObj As Control

    On Error Resume Next
    Set oTempObj = Ctl.Parent
    With tTopLeft
        Select Case True
             Case oTempObj Is Nothing
                .X = PTtoPX(Ctl.Left - UF.ScrollLeft * UF.Zoom / 100, False)
                .Y = PTtoPX(Ctl.Top - UF.ScrollTop * UF.Zoom / 100, True)
                ClientToScreen hwnd, tTopLeft
             Case TypeName(oTempObj) = "Frame"
                GetWindowRect oTempObj.[_GethWnd], tRect
                .X = PTtoPX(Ctl.Left - oTempObj.ScrollLeft * (oTempObj.Zoom / 100), False) + tRect.Left + 2
                .Y = PTtoPX(Ctl.Top - oTempObj.ScrollTop * (oTempObj.Zoom / 100), True) + tRect.Top + 8
            Case TypeName(oTempObj) = "Page"
                Set oMultiPage = oTempObj.Parent
                GetWindowRect GetNextWindow(oMultiPage.[_GethWnd], 5), tRect
                .X = PTtoPX(Ctl.Left - oTempObj.ScrollLeft * (oTempObj.Zoom / 100), False) + tRect.Left
                .Y = PTtoPX(Ctl.Top - oTempObj.ScrollTop * (oTempObj.Zoom / 100), True) + tRect.Top
                Set oMultiPage = Nothing
            End Select
        End With
    GetRealCtrlScreenLocation = tTopLeft
    Set oTempObj = Nothing
End Function

Private Function GetActiveComboBox(ByVal Ctl As Object) As Control
    Dim oCtl As Object
    Dim lCur As Long
    On Error Resume Next
    For Each oCtl In Ctl.Controls
        Err.Clear
        lCur = oCtl.CurX
        If Err.Number = 0 And TypeName(oCtl) = "ComboBox" Then Set GetActiveComboBox = oCtl: Exit Function
    Next
End Function

Private Function LoWord(ByVal Word As Long) As Integer
    Dim X As LongToInteger
    CopyMemory X, Word, LenB(X)
    LoWord = X.Low
End Function

Private Function ScreenDPI(ByVal bVert As Boolean) As Long
    Static lDPI(1), lDC
    If lDPI(0) = 0 Then
        lDC = GetDC(0)
        lDPI(0) = GetDeviceCaps(lDC, LOGPIXELSX)
        lDPI(1) = GetDeviceCaps(lDC, LOGPIXELSY)
        lDC = ReleaseDC(0, lDC)
    End If
    ScreenDPI = lDPI(Abs(bVert))
End Function

Private Function PTtoPX(ByVal Points As Single, ByVal bVert As Boolean) As Long
    PTtoPX = Points * ScreenDPI(bVert) / POINTSPERINCH
End Function

2- Code in the UserForm Module:
Code:
Option Explicit

Private Sub UserForm_Activate()
    Dim i As Long
    
    [B][COLOR=#008000]'Populate the controls[/COLOR][/B]
    For i = 0 To 100
        With ListBox1
            .ColumnCount = 4
            .ColumnWidths = "100;100;100;100"
            .AddItem "COLUMN1"
            .List(i, 1) = "COLUMN2"
            .List(i, 2) = "COLUMN3"
            .List(i, 3) = "COLUMN4"
        End With
        ListBox2.AddItem i
        ComboBox1.AddItem i
        ComboBox2.AddItem i
        ComboBox3.AddItem i
        ComboBox4.AddItem i
        ComboBox5.AddItem i
        ComboBox6.AddItem i
        ComboBox7.AddItem i
        ComboBox8.AddItem i
        ComboBox9.AddItem i
    Next i
    With TextBox1
        .Text = .Text & String(300, "A")
        .Text = .Text & String(300, "I")
        .Text = .Text & String(300, "X")
    End With
    Label1.Caption = "Object :"
    Label2.Caption = "Wheel Rotation :"
    Label3.Caption = "Scroll Direction :"
    Label4.Caption = "Cursor X :"
    Label5.Caption = "Cursor Y :"
    Label6.Caption = "Scroll Cancelled :"
    
    [B][COLOR=#008000]'Hook MouseWheel Scroll of Form and of all its controls[/COLOR][/B]
    Call HookMouseWheelScroll(Me)

End Sub
Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    Call RemoveMouseWheelHook
End Sub
Private Sub CommandButton1_Click()
    Unload Me
End Sub
[B][COLOR=#008000]
'-------------------------[/COLOR][/B]
[B][COLOR=#008000]'Public Generic event[/COLOR][/B]
[B][COLOR=#008000]'-------------------------[/COLOR][/B]

Public Sub OnScrollEvent(ByVal Obj As Object, ByVal WheelRotation As WHEEL_ROTATION, _
ByVal CtrlKey As CTRL_KEY_PRESS_STATE, ByVal X As Long, ByVal Y As Long, Cancel As Boolean)

    Dim sObjName As String, sWheelRot As String, sCtrlKey As String
    Dim sCurX As String, sCurY As String, sCancelScrol As String
    
    sObjName = "Object :  (" & Obj.Name & ")"
    sWheelRot = "Wheel Rotation :  (" & IIf(WheelRotation = Forward, "Forward", "Backward") & ")"
    sCtrlKey = "Scroll Direction :  (" & IIf(CtrlKey = Released, "Vert", "Horiz") & ")"
    sCurX = "Cursor X :  (" & X & ")"
    sCurY = "Cursor Y :  (" & Y & ")"
    sCancelScrol = "Scroll Cancelled :  (" & Cancel & ")"
    
    Label1.Caption = sObjName
    Label2.Caption = sWheelRot
    Label3.Caption = sCtrlKey
    Label4.Caption = sCurX
    Label5.Caption = sCurY
    Label6.Caption = sCancelScrol
End Sub
 
Just remembered: When the code is running, VeryHidden sheets do show up in hidden sheets list. Can anyone confirm is it so or due to some change I have made to the original code?
When you set something to xlVeryHidden is doesn’t show up in the hidden tabs list.
Can you share a bit more on how to modify the code to get scroll up / down working again? (Your #3)
 
Upvote 0

Excel Facts

Lock one reference in a formula
Need 1 part of a formula to always point to the same range? use $ signs: $V$2:$Z$99 will always point to V2:Z99, even after copying
When you set something to xlVeryHidden is doesn’t show up in the hidden tabs list.
They shouldn't but they do! :)

I can't say how you can do it, as I myself am not sure about what I did. Jaafar says it works on both 32 and 64 bit but wasn't working as expected on my PC. This works for me in 64-bit Excel O365.

I just copy pasted the functions (in my earlier post) to the module code. And changed:

VBA Code:
                If (hiword(CLng(tMsg.wParam)) / WHEEL_DELTA) > 0 Or (hiword(CLng(tMsg.wParam)) = WHEEL_DELTA) Then
                    WheelRotation = Forward
                Else
                    WheelRotation = Backward
                End If

with

VBA Code:
#If Win64 Then
    If HighWord64(tMsg.wParam) > (2 ^ 15) Then
        If (HighWord64(tMsg.wParam) - (2 ^ 16)) < 0 Then
            WheelRotation = Backward
        End If
    ElseIf HighWord64(tMsg.wParam) > 0 Then
        WheelRotation = Forward
    End If
#Else
    If HighWord32(CLng(tMsg.wParam)) > 0 Then
        WheelRotation = Forward
    Else
        WheelRotation = Backward
    End If
#End If
 
Upvote 0
Just remembered: When the code is running, VeryHidden sheets do show up in hidden sheets list. Can anyone confirm is it so or due to some change I have made to the original code?

That seems to be a bug.
Simply running the following code makes VeryHidden sheets show up in the list.
VBA Code:
Do
  DoEvents
Loop

One workaround is to temporarly protect the structure of the workbook before loading the userform and then unprotect it when done.
ThisWorkbook.Protect Structure:=True

The above will only affect this workbook not other open workbooks.
 
Upvote 0
Hello, first post here!
I use a workbook with many modeless userforms and I'm currently using your code as this is the only one I found that allow scrolling on modeless forms.
@Jaafar Tribak Really nice work!

I'm only a self-taught vba coder so I'm really far from understanding everything but the only downside I found is a pseudo-lockdown when using multiple modeless userforms.

I'll try to give a clear explanation.
First I'm using win7 (and 10 on a second computer) 64 bits as well as office 2013.
When I open multiple modeless forms (some with scrolling, others without), I sometime encounter some kind of lockdown during the Do loop if I switch (activate) from one form to another of if I close the active form using the cross (but it does not happen if using a command button to unload it). I say some kind of lockdown because the form is still responsive to keyboard inputs but I can't click any of its activeX buttons. By pushing escape and breaking into debugger I found that the code hangs on the "Peakmessage" line.

I tried to solve this by adding a check at the beginning of the loop
If GetActiveWindow <> hwnd Or UserForm Is Nothing Then Exit Do
and by setting focus to the form before the "Waitmessage" line with
Call SendMessage(hwnd, &H7, 0&, 0&)
It seems to work most of the time but still (rarely) get a lockdown.

Stange thing is that only occurs once, if I break into the debugger and F8 the loop exits thanks to the added line and if I try the same operation it does not occur anymore.
It seems to only happens if I switch too fast between windows. If I leave a second or two before switching it works as intended.

Thanks for your hard work!

NB: sorry if it's a bit confuse I'm from France.
Regards.
 
Upvote 0
@krevett62

Running multiple userforms with this code will be problematic because of the running loop.
I will take a look and see if i can adapt the code so that it works with multiple userforms.
I will post the result later.
 
Upvote 0
@Jaafar Tribak well I must say it works well for what I want to do, the loop don't consume too much (it's for a personal entertainment project) the CPU usage never goes beyond 3-4% on i5 6600K slightly overclocked. And I only encounter this lock down if I switch too fast, now that I'm aware of it, I always wait one or two seconds before closing/switching multiple userforms and it seems to work well (and I can always break to the debugger so no need to ctrl+alt+suppr)

Thanks for your work and support!
 
Upvote 0
I have replaced the PeekMessage api with GetMessage api and replaced the loop with a windows timer so that the code now works with multiple userforms.

Tested in excel 2016 x64bit - OS: win10 64Bit ... Worked quite smoothly.


Workbook example







1- API code in a Standard Module:
VBA Code:
Option Explicit

Public Enum CTRL_KEY_PRESS_STATE
    Released
    Pressed
End Enum

Public Enum WHEEL_ROTATION
    Forward
    Backward
End Enum

Private Type POINTAPI
    X As Long
    Y As Long
End Type

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

#If Win64 Then
    Private Type MSG
        hwnd As LongLong
        message As Long
        wParam As LongLong
        lParam As LongLong
        time As Long
        pt As POINTAPI
    End Type
#Else
    Private Type MSG
        hwnd As Long
        message As Long
        wParam As Long
        lParam As Long
        time As Long
        pt As POINTAPI
    End Type
#End If
   
#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongPtr) As LongPtr
    #Else
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As Any, pvarChild As Variant) As Long
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As LongPtr
    #End If
    Private Declare PtrSafe Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow 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 EnumWindows Lib "user32" (ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Long
    Private Declare PtrSafe Function SetTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr
    Private Declare PtrSafe Function KillTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long
    Private Declare PtrSafe Function GetMessage Lib "user32" Alias "GetMessageA" (lpMsg As MSG, ByVal hwnd As LongPtr, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long) As Long
    Private Declare PtrSafe Function TranslateMessage Lib "user32" (lpMsg As MSG) As Long
    Private Declare PtrSafe Function DispatchMessage Lib "user32" Alias "DispatchMessageA" (lpMsg As MSG) As LongPtr
    Private Declare PtrSafe Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function ScreenToClient Lib "user32" (ByVal hwnd As LongPtr, lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare PtrSafe Function GetAncestor Lib "user32" (ByVal hwnd As LongPtr, ByVal gaFlags As Long) As LongPtr
    Private Declare PtrSafe Function InvalidateRect Lib "user32" (ByVal hwnd As LongPtr, ByVal lpRect As Long, ByVal bErase As Long) As Long
    Private Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
    Private Declare PtrSafe Function UpdateWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function GetDesktopWindow Lib "user32" () As LongPtr

    Private hwnd As LongPtr, hObjUnderMouse As LongPtr, Ptr As LongPtr
#Else
    Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
    Private Declare Function AccessibleObjectFromPoint Lib "Oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hwnd As Long) As Long
    Private Declare Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow 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 EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
    Private Declare Function SetTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
    Private Declare Function KillTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
    Private Declare Function GetMessage Lib "user32" Alias "GetMessageA" (lpMsg As MSG, ByVal hwnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long) As Long
    Private Declare Function TranslateMessage Lib "user32" (lpMsg As MSG) As Long
    Private Declare Function DispatchMessage Lib "user32" Alias "DispatchMessageA" (lpMsg As MSG) As Long
    Private Declare Function GetClientRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
    Private Declare Function ScreenToClient Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Private Declare Function GetAncestor Lib "user32" (ByVal hwnd As Long, ByVal gaFlags As Long) As Long
    Private Declare Function InvalidateRect Lib "user32" (ByVal hwnd As Long, ByVal lpRect As Long, ByVal bErase As Long) As Long
    Private Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
    Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function GetDesktopWindow Lib "user32" () As Long
   
    Private hwnd As Long, hObjUnderMouse As Long
#End If

Private oCurrentUserForm As Object, oCurrentIgnoreList As Variant
Private oCollection As Collection
Private objUnderMouse As Object

Private WheelRotation As WHEEL_ROTATION
Private CtrlKey As CTRL_KEY_PRESS_STATE
Private tMsg As MSG
Private tCurPos As POINTAPI, tPt As POINTAPI, tClient As RECT
Private oIA As IAccessible, oIACtrl As IAccessible, oIAPage As IAccessible
Private oTempCtrl As Control, oCtrl As Control, oTempPage As Control
Private vKid  As Variant
Private lLeft As Long, lTop As Long, lResult As Long, i As Long
Private bCancel As Boolean


Public Property Let EnableWheelScroll(ByVal UserForm As Object, Optional IgnoreList As Variant, ByVal Enable As Boolean)

    Call KillTimer(hwnd, 0)
    If Enable = False Then
        Set oCollection = Nothing
        Call RefreshScreen
    Else
        Set oCurrentUserForm = UserForm
        oCurrentIgnoreList = IgnoreList
        Call IUnknown_GetWindow(UserForm, VarPtr(hwnd))
        Set oCollection = New Collection
        Call SetTimer(hwnd, 0, 0, AddressOf TimerProc)
    End If

End Property


'________________________________PRIVATE SUBS___________________________________

Private Sub TimerProc()

    Const SCROLL_CHANGE = 20     ' <== Change Const as required '//
    '/////////////////////////////////////////////////////////////

    Const CHILDID_SELF = &H0&
    Const S_OK As Long = &H0
    Const WM_NCLBUTTONDOWN = &HA1
    Const WM_TIMER = &H113
    Const WM_MOUSEWHEEL = &H20A
    Const WHEEL_DELTA = 120
    Const PM_REMOVE = &H1
    Const MK_CONTROL = &H8
    Const GA_ROOT = 2
    Const POINTSPERINCH As Long = 72
    Const LOGPIXELSX As Long = 88
    Const LOGPIXELSY As Long = 90
   

    On Error Resume Next
   
    'RETRIEVE AND STORE THE LOCATION OF EACH CONTROL.
    For Each oIACtrl In oCurrentUserForm.Controls
        Set oTempCtrl = oIACtrl
        If IsError(Application.Match(TypeName(oTempCtrl), oCurrentIgnoreList, 0)) Then
            Call oIACtrl.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
            If TypeName(oTempCtrl) = "MultiPage" Then
                Set oIAPage = oTempCtrl.Pages(oTempCtrl.Value)
                Call oIAPage.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
                Set oTempPage = oIAPage
                oCollection.Add oTempPage, CStr(lLeft & lTop & oTempCtrl.Name & oTempCtrl.Pages(oTempCtrl.Value).Caption)
            End If
            oCollection.Add oTempCtrl, CStr(lLeft & lTop)
        End If
    Next
       
    'RETRIEVE THE LOCATION OF THE CONTROL CURRENTLY UNDER THE MOUSE POINTER.
    Call GetCursorPos(tCurPos)
    #If Win64 Then
        Call CopyMemory(Ptr, tCurPos, LenB(tCurPos))
        lResult = AccessibleObjectFromPoint(Ptr, oIA, vKid)
        hObjUnderMouse = WindowFromPoint(Ptr)
    #Else
        lResult = AccessibleObjectFromPoint(tCurPos.X, tCurPos.Y, oIA, vKid)
        hObjUnderMouse = WindowFromPoint(tCurPos.X, tCurPos.Y)
    #End If
       
    If lResult = S_OK Then
   
        Call oIA.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
        Set objUnderMouse = oCollection.Item(lLeft & lTop)
       
        If GetAncestor(hObjUnderMouse, GA_ROOT) <> hwnd Then
            If TypeName(objUnderMouse) <> "ComboBox" Then
                Exit Sub
            End If
        End If
       
        For Each oCtrl In oCurrentUserForm.Controls
            If TypeName(oCtrl) = "MultiPage" Then
                Set objUnderMouse = oCollection.Item(lLeft & lTop & oCtrl.Name & oCtrl.Pages(oCtrl.Value).Caption)
            End If
        Next
       
        If oIA.accName(CHILDID_SELF) = oCurrentUserForm.Caption Then
            Set objUnderMouse = oCurrentUserForm
        End If
       
        'WAIT FOR A MOUSEWHEEL-SCROLL AND RAISE THE SCROLL PSEUDO-EVENT WHEN IT HAPPENS.
        If Not objUnderMouse Is Nothing Then
       
            Call GetMessage(tMsg, hwnd, 0, 0)
           
            'EXIT TIMER PROC WHEN MOVING THE FORM.
            If tMsg.message = WM_NCLBUTTONDOWN Then
                Call KillTimer(hwnd, 0)
                Call TranslateMessage(tMsg)
                Call DispatchMessage(tMsg)
                GoTo Xit
            End If
               
            tPt = tMsg.pt
            Call GetClientRect(tMsg.hwnd, tClient)
            Call ScreenToClient(hwnd, tPt)
           
              If GetAsyncKeyState(vbKeyLButton) = 0 And tPt.Y <= 0 Then
                Call KillTimer(hwnd, 0)
                GoTo Xit
              End If
           
            'EXIT TIMER PROC WHEN MOVING THE FORM.
            If tPt.Y <= 0 Then
                If tMsg.message = WM_TIMER Then
                    Call KillTimer(hwnd, 0)
                    Call TranslateMessage(tMsg)
                    Call DispatchMessage(tMsg)
                    GoTo Xit
                End If
            End If

            If tMsg.message = WM_MOUSEWHEEL Then
           
                CtrlKey = IIf(loword(CLng(tMsg.wParam)) = MK_CONTROL, Pressed, Released)
       
                If (hiword(CLng(tMsg.wParam)) / WHEEL_DELTA) > 0 Or (hiword(CLng(tMsg.wParam)) = WHEEL_DELTA) Then
                    WheelRotation = Forward
                Else
                    WheelRotation = Backward
                End If
               
                'RAISE THE PSEUDO-SCROLL EVENT LOCATED IN THE oCurrentUserForm MODULE.
                Call oCurrentUserForm.OnMouseWheelScroll(objUnderMouse, WheelRotation, CtrlKey, tCurPos.X - lLeft, tCurPos.Y - lTop, bCancel)
               
                'IF SCROLL EVENT NOT CANCELED FOR THE CURRENT CONTROL, GO AHEAD AND IMPLEMENT THE SCROLLING.
                If Not bCancel Then
               
                    If TypeName(objUnderMouse) = "TextBox" Then
                        With objUnderMouse
                            .SetFocus
                            If i = 0 Then
                                .SelStart = 0
                            Else
                                .SelStart = IIf(.SelStart = .LineCount, 0, .SelStart)
                            End If
                            If WheelRotation = Forward Then
                                .CurLine = .CurLine - 1
                            Else
                                .CurLine = IIf(.CurLine = .LineCount - 1, .CurLine, .CurLine + 1)
                            End If
                        End With
                        i = i + 1
                    End If
                   
                    If TypeName(objUnderMouse) = "ScrollBar" Then
                        With objUnderMouse
                            If WheelRotation = Forward Then
                                .Value = IIf(.Value - objUnderMouse.SmallChange > .Min, .Value - objUnderMouse.SmallChange, .Min)
                            Else
                                .Value = IIf(.Value + objUnderMouse.SmallChange < .Max, .Value + objUnderMouse.SmallChange, .Max)
                            End If
                        End With
                    End If
                   
                    If TypeName(objUnderMouse) = "ListBox" Or TypeName(objUnderMouse) = "ComboBox" Then
                   
                        With objUnderMouse
                            If CtrlKey = Released Then
                                If WheelRotation = Forward Then
                                .TopIndex = .TopIndex - 1
                                Else
                                .TopIndex = .TopIndex + 1
                                End If
                            Else
                                .SetFocus
                                If WheelRotation = Forward Then
                                    SendKeys "{LEFT}", True
                                    DoEvents
                                    SendKeys "{RIGHT}", True
                                Else
                                    SendKeys "{RIGHT}", True
                                    DoEvents
                                    SendKeys "{RIGHT}", True
                                End If
                            End If
                        End With
                       
                    End If
                   
                    If TypeName(objUnderMouse) <> "ComboBox" Then
                        Call EnumWindows(AddressOf HideDropDown, ByVal 0)
                    End If
                   
                    With objUnderMouse
                        If CtrlKey = Released Then
                            If WheelRotation = Forward Then
                                .ScrollTop = Application.Max(0, .ScrollTop - SCROLL_CHANGE)
                            Else
                                .ScrollTop = Application.Min(.ScrollHeight - .InsideHeight, .ScrollTop + SCROLL_CHANGE)
                            End If
                        Else
                            If WheelRotation = Forward Then
                                .ScrollLeft = Application.Max(0, .ScrollLeft - SCROLL_CHANGE)
                            Else
                                .ScrollLeft = Application.Min(.ScrollWidth - .InsideWidth, .ScrollLeft + SCROLL_CHANGE)
                            End If
                        End If
                    End With
                End If
            End If
        End If
    End If

    Call TranslateMessage(tMsg)
    Call DispatchMessage(tMsg)
    Call RefreshScreen
    Exit Sub

Xit:

    Call RefreshScreen
    Call SetTimer(hwnd, 0, 0, AddressOf TimerProc)

End Sub


Private Function loword(DWord As Long) As Integer
    If DWord And &H8000& Then
        loword = DWord Or &HFFFF0000
    Else
        loword = DWord And &HFFFF&
    End If
End Function

Private Function hiword(ByVal DWord As Long) As Integer
    hiword = (DWord And &HFFFF0000) \ &H10000
End Function

#If Win64 Then
    Private Function HideDropDown(ByVal hwnd As LongLong, ByVal lParam As Long) As Long
#Else
    Private Function HideDropDown(ByVal hwnd As Long, ByVal lParam As Long) As Long
#End If

    Dim sClassName As String * 256
   
    Call GetClassName(hwnd, sClassName, 256)
    If Left(sClassName, 2) = "F3" Then
        Call ShowWindow(hwnd, 0)
        HideDropDown = 0
        Exit Function
    End If
    HideDropDown = 1
   
End Function

Private Sub RefreshScreen()
    Call InvalidateRect(Application.hwnd, 0, 0)
    Call UpdateWindow(Application.hwnd)
    Call InvalidateRect(FindWindowEx(FindWindowEx(Application.hwnd, 0&, "XLDESK", vbNullString), 0&, "EXCEL7", vbNullString), 0, 0)
    Call UpdateWindow(FindWindowEx(FindWindowEx(Application.hwnd, 0&, "XLDESK", vbNullString), 0&, "EXCEL7", vbNullString))
    Call InvalidateRect(GetDesktopWindow, 0, 0)
    Call UpdateWindow(GetDesktopWindow)
End Sub




2- Code in the UserForms as per workbook example: (Both, UserForm1 and UserForm2 codes - Adapt as required)
VBA Code:
Option Explicit

Private Sub UserForm_Activate()
   
    Dim i As Long

    For i = 1 To 200
        Me.ListBox1.AddItem i
        Me.ComboBox1.AddItem i
    Next i

    EnableWheelScroll(Me) = True
   
End Sub

Private Sub UserForm_Terminate()

    EnableWheelScroll(Me) = False
   
    With Sheet1
        .[a10].ClearContents
        .[a13].ClearContents
        .[a16].ClearContents
        .[a19].ClearContents
        .[a22].ClearContents
        .[a25].ClearContents
    End With
   
End Sub

Private Sub CommandButton1_Click()
    UserForm2.Show vbModeless
End Sub

Private Sub CommandButton2_Click()
    Unload Me
End Sub


'--------------------
'Public Generic event
'Set the Cancel Argument to TRUE to disable scrolling
Public Sub OnMouseWheelScroll(ByVal obj As Object, ByVal WheelRotation As WHEEL_ROTATION, _
ByVal CtrlKey As CTRL_KEY_PRESS_STATE, ByVal X As Long, ByVal Y As Long, Cancel As Boolean)

    With Sheet1
        If TypeName(obj) = "Page" Then
            .[a10] = obj.Parent.Name & "." & obj.Name
        Else
            .[a10] = obj.Name
        End If
        .[a13] = IIf(WheelRotation = Forward, "Forward", "Backward")
        .[a16] = IIf(CtrlKey = Pressed, "Pressed", "Released")
        .[a19] = IIf(CtrlKey = Pressed, "Horizontal", "Vertical")
        .[a22] = X
        .[a25] = Y
    End With

End Sub
 
Upvote 0
Here is a much improved version for multiple userforms:

Enhancements list:
A- Improves the slightly sluggish feel when fast moving and switching the userforms.
B- Prevents the occasional freezing of the screen after unloading the userforms. (may need more attention)
C- Bug fixed in previous code which was causing control scrollbars to freeze intermittently.
D- A new argument (Byval UserForm aAs Object) added to the generic "OnMouseWheelScroll" pseudo-event.
E- No more risk of crashing the application (due to the use of a windows timer) should an unhandled error occur or a loss of state.

Workbook Example


1- Final API code in a standard module:
VBA Code:
Option Explicit

Public Enum CTRL_KEY_PRESS_STATE
    Released
    Pressed
End Enum

Public Enum WHEEL_ROTATION
    Forward
    Backward
End Enum

Private Type POINTAPI
    X As Long
    Y As Long
End Type

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

#If Win64 Then
    Private Type MSG
        hwnd As LongLong
        message As Long
        wParam As LongLong
        lParam As LongLong
        time As Long
        pt As POINTAPI
    End Type
#Else
    Private Type MSG
        hwnd As Long
        message As Long
        wParam As Long
        lParam As Long
        time As Long
        pt As POINTAPI
    End Type
#End If
  
#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongPtr) As LongPtr
        Private Declare PtrSafe Function PtInRect Lib "user32" (lpRect As RECT, ByVal arg2 As LongPtr) As Long
    #Else
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As Any, pvarChild As Variant) As Long
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As LongPtr
        Private Declare PtrSafe Function PtInRect Lib "user32" (lpRect As RECT, ByVal arg1 As Long, ByVal arg2 As Long) As Long
    #End If
    Private Declare PtrSafe Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow 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 EnumWindows Lib "user32" (ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Long
    Private Declare PtrSafe Function SetTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr
    Private Declare PtrSafe Function KillTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long
    Private Declare PtrSafe Function GetMessage Lib "user32" Alias "GetMessageA" (lpMsg As MSG, ByVal hwnd As LongPtr, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long) As Long
    Private Declare PtrSafe Function TranslateMessage Lib "user32" (lpMsg As MSG) As Long
    Private Declare PtrSafe Function DispatchMessage Lib "user32" Alias "DispatchMessageA" (lpMsg As MSG) As LongPtr
    Private Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function ScreenToClient Lib "user32" (ByVal hwnd As LongPtr, lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Function GetAncestor Lib "user32" (ByVal hwnd As LongPtr, ByVal gaFlags As Long) As LongPtr
    Private Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer

    Private hwnd As LongPtr, hObjUnderMouse As LongPtr, lPtr As LongPtr
#Else
    Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
    Private Declare Function AccessibleObjectFromPoint Lib "Oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Function PtInRect Lib "user32" (lpRect As RECT, ByVal arg1 As Long, ByVal arg2 As Long) As Long
    Private Declare Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hwnd As Long) As Long
    Private Declare Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow 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 EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
    Private Declare Function SetTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
    Private Declare Function KillTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
    Private Declare Function GetMessage Lib "user32" Alias "GetMessageA" (lpMsg As MSG, ByVal hwnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long) As Long
    Private Declare Function TranslateMessage Lib "user32" (lpMsg As MSG) As Long
    Private Declare Function DispatchMessage Lib "user32" Alias "DispatchMessageA" (lpMsg As MSG) As Long
    Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
    Private Declare Function GetClientRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
    Private Declare Function ScreenToClient Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
    Private Declare Function GetAncestor Lib "user32" (ByVal hwnd As Long, ByVal gaFlags As Long) As Long
    Private Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
  
    Private hwnd As Long, hObjUnderMouse As Long
#End If

Private oCurrentUserForm As Object, oCurrentIgnoreList As Variant
Private oCollection As Collection
Private objUnderMouse As Object

Private WheelRotation As WHEEL_ROTATION
Private CtrlKey As CTRL_KEY_PRESS_STATE
Private tMsg As MSG
Private tCurPos As POINTAPI, tPt As POINTAPI, tWinRect As RECT, tClient As RECT
Private oIA As IAccessible, oIACtrl As IAccessible, oIAPage As IAccessible
Private oTempCtrl As Control, oCtrl As Control, oTempPage As Control
Private vKid  As Variant
Private lLeft As Long, lTop As Long, lAccResult As Long, lPtInRectlResult As Long, i As Long
Private bCancel As Boolean


Public Property Let EnableWheelScroll(ByVal UserForm As Object, Optional IgnoreList As Variant, ByVal Enable As Boolean)

    Call KillTimer(hwnd, 0)
    If Enable = False Then
        Set oCollection = Nothing
    Else
        Set oCurrentUserForm = UserForm
        oCurrentIgnoreList = IgnoreList
        Call IUnknown_GetWindow(UserForm, VarPtr(hwnd))
        Set oCollection = New Collection
        Call SetTimer(hwnd, 0, 0, AddressOf TimerProc)
    End If

End Property



'________________________________PRIVATE SUBS___________________________________

Private Sub TimerProc()

    Const SCROLL_CHANGE = 20     ' <== Change Const as required '//
    '/////////////////////////////////////////////////////////////

    Const CHILDID_SELF = &H0&
    Const S_OK As Long = &H0
    Const WM_NCLBUTTONDOWN = &HA1
    Const WM_TIMER = &H113
    Const WM_MOUSEWHEEL = &H20A
    Const WHEEL_DELTA = 120
    Const PM_REMOVE = &H1
    Const MK_CONTROL = &H8
    Const GA_ROOT = 2
    Const POINTSPERINCH As Long = 72
    Const LOGPIXELSX As Long = 88
    Const LOGPIXELSY As Long = 90
  

    On Error Resume Next
  
    'RETRIEVE AND STORE THE LOCATION OF EACH CONTROL.
    For Each oIACtrl In oCurrentUserForm.Controls
        Set oTempCtrl = oIACtrl
        If IsError(Application.Match(TypeName(oTempCtrl), oCurrentIgnoreList, 0)) Then
            Call oIACtrl.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
            If TypeName(oTempCtrl) = "MultiPage" Then
                Set oIAPage = oTempCtrl.Pages(oTempCtrl.Value)
                Call oIAPage.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
                Set oTempPage = oIAPage
                oCollection.Add oTempPage, CStr(lLeft & lTop & oTempCtrl.Name & oTempCtrl.Pages(oTempCtrl.Value).Caption)
            End If
            oCollection.Add oTempCtrl, CStr(lLeft & lTop)
        End If
    Next
      
    'RETRIEVE ELEMENTS UNDER THE MOUSE POINTER.
    Call GetCursorPos(tCurPos)
    Call GetWindowRect(hwnd, tWinRect)
  
    #If Win64 Then
        Call CopyMemory(lPtr, tCurPos, LenB(tCurPos))
        lAccResult = AccessibleObjectFromPoint(lPtr, oIA, vKid)
        hObjUnderMouse = WindowFromPoint(lPtr)
        lPtInRectlResult = PtInRect(tWinRect, lPtr)
    #Else
        lAccResult = AccessibleObjectFromPoint(tCurPos.X, tCurPos.Y, oIA, vKid)
        hObjUnderMouse = WindowFromPoint(tCurPos.X, tCurPos.Y)
        lPtInRectlResult = PtInRect(tWinRect, tCursPos.X, tCursPos.Y)
    #End If
  
    'EXIT TIMER PROC IF MOUSE OUTSIDE FORM RECT.    
    If lPtInRectlResult = 0 Then
        Call KillTimer(hwnd, 0)
        GoTo Xit
    End If
 
    If lAccResult = S_OK Then
  
        Call oIA.accLocation(lLeft, lTop, 0, 0, CHILDID_SELF)
        Set objUnderMouse = oCollection.Item(lLeft & lTop)
      
        If GetAncestor(hObjUnderMouse, GA_ROOT) <> hwnd Then
            If TypeName(objUnderMouse) <> "ComboBox" Then
                Exit Sub
            End If
        End If
      
        For Each oCtrl In oCurrentUserForm.Controls
            If TypeName(oCtrl) = "MultiPage" Then
                Set objUnderMouse = oCollection.Item(lLeft & lTop & oCtrl.Name & oCtrl.Pages(oCtrl.Value).Caption)
            End If
        Next
      
        If oIA.accName(CHILDID_SELF) = oCurrentUserForm.Caption Then
            Set objUnderMouse = oCurrentUserForm
        End If
      
        'WAIT FOR A MOUSEWHEEL-SCROLL AND RAISE THE SCROLL PSEUDO-EVENT WHEN IT HAPPENS.
        If Not objUnderMouse Is Nothing Then
      
            Call GetMessage(tMsg, 0, 0, 0)
          
            'EXIT TIMER PROC WHEN MOVING THE FORM.
            If tMsg.message = WM_NCLBUTTONDOWN Then
                Call KillTimer(hwnd, 0)
                Call TranslateMessage(tMsg)
                Call DispatchMessage(tMsg)
                GoTo Xit
            End If
              
            tPt = tMsg.pt
            Call GetClientRect(hwnd, tClient)
            Call ScreenToClient(hwnd, tPt)
          
            If GetAsyncKeyState(vbKeyLButton) = 0 And tPt.Y <= 0 Then
                Call KillTimer(hwnd, 0)
                GoTo Xit
            End If
          
            'EXIT TIMER PROC WHEN MOVING THE FORM.
            If tPt.Y <= 0 Then
                If tMsg.message = WM_TIMER Then
                    Call KillTimer(hwnd, 0)
                    Call TranslateMessage(tMsg)
                    Call DispatchMessage(tMsg)
                    GoTo Xit
                End If
            End If

            If tMsg.message = WM_MOUSEWHEEL Then
          
                CtrlKey = IIf(loword(CLng(tMsg.wParam)) = MK_CONTROL, Pressed, Released)
      
                If (hiword(CLng(tMsg.wParam)) / WHEEL_DELTA) > 0 Or (hiword(CLng(tMsg.wParam)) = WHEEL_DELTA) Then
                    WheelRotation = Forward
                Else
                    WheelRotation = Backward
                End If
              
                'RAISE THE PSEUDO-SCROLL EVENT LOCATED IN THE oCurrentUserForm MODULE.
                Call oCurrentUserForm.OnMouseWheelScroll(oCurrentUserForm, objUnderMouse, WheelRotation, CtrlKey, tCurPos.X - lLeft, tCurPos.Y - lTop, bCancel)
              
                'IF SCROLL EVENT NOT CANCELED FOR THE CURRENT CONTROL, GO AHEAD AND IMPLEMENT THE SCROLLING.
                If Not bCancel Then
              
                    If TypeName(objUnderMouse) = "TextBox" Then
                        With objUnderMouse
                            .SetFocus
                            If i = 0 Then
                                .SelStart = 0
                            Else
                                .SelStart = IIf(.SelStart = .LineCount, 0, .SelStart)
                            End If
                            If WheelRotation = Forward Then
                                .CurLine = .CurLine - 1
                            Else
                                .CurLine = IIf(.CurLine = .LineCount - 1, .CurLine, .CurLine + 1)
                            End If
                        End With
                        i = i + 1
                    End If
                  
                    If TypeName(objUnderMouse) = "ScrollBar" Then
                        With objUnderMouse
                            If WheelRotation = Forward Then
                                .Value = IIf(.Value - objUnderMouse.SmallChange > .Min, .Value - objUnderMouse.SmallChange, .Min)
                            Else
                                .Value = IIf(.Value + objUnderMouse.SmallChange < .Max, .Value + objUnderMouse.SmallChange, .Max)
                            End If
                        End With
                    End If
                  
                    If TypeName(objUnderMouse) = "ListBox" Or TypeName(objUnderMouse) = "ComboBox" Then
                  
                        With objUnderMouse
                            If CtrlKey = Released Then
                                If WheelRotation = Forward Then
                                .TopIndex = .TopIndex - 1
                                Else
                                .TopIndex = .TopIndex + 1
                                End If
                            Else
                                .SetFocus
                                If WheelRotation = Forward Then
                                    SendKeys "{LEFT}", True
                                    DoEvents
                                    SendKeys "{RIGHT}", True
                                Else
                                    SendKeys "{RIGHT}", True
                                    DoEvents
                                    SendKeys "{RIGHT}", True
                                End If
                            End If
                        End With
                      
                    End If
                  
                    If TypeName(objUnderMouse) <> "ComboBox" Then
                        Call EnumWindows(AddressOf HideDropDown, ByVal 0)
                    End If
                  
                    With objUnderMouse
                        If CtrlKey = Released Then
                            If WheelRotation = Forward Then
                                .ScrollTop = Application.Max(0, .ScrollTop - SCROLL_CHANGE)
                            Else
                                .ScrollTop = Application.Min(.ScrollHeight - .InsideHeight, .ScrollTop + SCROLL_CHANGE)
                            End If
                        Else
                            If WheelRotation = Forward Then
                                .ScrollLeft = Application.Max(0, .ScrollLeft - SCROLL_CHANGE)
                            Else
                                .ScrollLeft = Application.Min(.ScrollWidth - .InsideWidth, .ScrollLeft + SCROLL_CHANGE)
                            End If
                        End If
                    End With
                  
                End If
            End If
        End If
    End If

    Call TranslateMessage(tMsg)
    Call DispatchMessage(tMsg)
  
    Exit Sub

Xit:
  
    Call SetTimer(hwnd, 0, 0, AddressOf TimerProc)

End Sub


Private Function loword(DWord As Long) As Integer
    If DWord And &H8000& Then
        loword = DWord Or &HFFFF0000
    Else
        loword = DWord And &HFFFF&
    End If
End Function

Private Function hiword(ByVal DWord As Long) As Integer
    hiword = (DWord And &HFFFF0000) \ &H10000
End Function

#If Win64 Then
    Private Function HideDropDown(ByVal hwnd As LongLong, ByVal lParam As Long) As Long
#Else
    Private Function HideDropDown(ByVal hwnd As Long, ByVal lParam As Long) As Long
#End If

    Dim sClassName As String * 256
  
    Call GetClassName(hwnd, sClassName, 256)
    If Left(sClassName, 2) = "F3" Then
        Call ShowWindow(hwnd, 0)
        HideDropDown = 0
        Exit Function
    End If
    HideDropDown = 1

End Function


2- Code in the UserForms as per workbook example: (Both, UserForm1 and UserForm2 codes - Adapt as required)
VBA Code:
Option Explicit

Private Sub UserForm_Initialize()
    Dim i As Long

    For i = 1 To 100
        Me.ListBox1.AddItem i
        Me.ComboBox1.AddItem i
    Next i
End Sub

Private Sub UserForm_Activate()
    EnableWheelScroll(Me) = True
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    EnableWheelScroll(Me) = False
    With Sheet1
        .[a9].ClearContents
        .[a12].ClearContents
        .[a15].ClearContents
        .[a18].ClearContents
        .[a21].ClearContents
        .[a24].ClearContents
        .[a27].ClearContents
    End With
End Sub

Private Sub CommandButton1_Click()
    UserForm2.Show vbModeless
End Sub

Private Sub CommandButton2_Click()
    Unload Me
End Sub

'--------------------
'Public Generic event
'Set the Cancel Argument to TRUE to disable scrolling
Public Sub OnMouseWheelScroll( _
    ByVal UserForm As Object, _
    ByVal obj As Object, _
    ByVal WheelRotation As WHEEL_ROTATION, _
    ByVal CtrlKey As CTRL_KEY_PRESS_STATE, _
    ByVal X As Long, _
    ByVal Y As Long, _
    ByRef Cancel As Boolean _
)

    With Sheet1
        If TypeName(obj) = "Page" Then
            .[a12] = obj.Parent.Name & "." & obj.Name
        Else
            .[a12] = obj.Name
        End If
        .[a9] = UserForm.Name
        .[a15] = IIf(WheelRotation = Forward, "Forward", "Backward")
        .[a18] = IIf(CtrlKey = Pressed, "Pressed", "Released")
        .[a21] = IIf(CtrlKey = Pressed, "Horizontal", "Vertical")
        .[a24] = X
        .[a27] = Y
    End With

End Sub


@Gokhan Aycan
As opposed to the previous Do Loop codes, this timer version doesn't cause the bug that makes VeryHidden sheets show up in the hidden sheets list.
 
Upvote 0
I am following this update with interest as I do have multiple (modeless) forms that require scrolling. Don't have the time to revise my code at the moment though. Thanks for the improvements.
 
Upvote 0
Tested your latest code and it's working smoothly for me with 3-4 modeless userform spread on two screens. I encountered no bugs or lockup (only small slowdown(s) when draging a window and moving it around the screen, but nothing really annoying).

That was quite a very quick update , thanks!
 
Upvote 0

Forum statistics

Threads
1,215,480
Messages
6,125,053
Members
449,206
Latest member
Healthydogs

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top