VBA- MouseMove to open and close another userform - excel

I have a userform with several label controls, all belong to a class that on mouseover, another userform containing some information about that label will be shown. Now I wanted that form to be closed after mouse leaves the control. Now I am using application.ontime and closing the second form after 2 seconds, which makes the form flickers when the mouse is still over the label. I am wondering if there is anyway better? Here is my code so far.
My Code on the class Module
Private Sub Label1_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, _
ByVal X As Single, ByVal Y As Single)
Dim m
On Error Resume Next
If Button = XlMouseButton.xlPrimaryButton And LabelBase.Edit.Caption = "Done" Then
Label1.Left = Label1.Left + X - x_offset
Label1.Top = Label1.Top + Y - y_offset
ElseIf LabelBase.Edit.Caption = "Edit" Then
With CurrentJob
.Caption = "Current Job of " & Label1.Caption
.LBcurr.list = openJobs
.LLast = LastJob
.LClsd = WorksheetFunction.CountIfs(oprecord.Range("e:e"), Label1.Caption, oprecord.Range("f:f"), Date, oprecord.Range("s:s"), "CLOSED")
.LAc = Fix(Right(Label1.Tag, Len(Label1.Tag) - 1) / 24) + 70006
m = WorksheetFunction.VLookup(Label1.Caption, rooster.Range("b:e"), 4, 0)
.LSkill = Right(m, Len(m) - InStr(1, m, " "))
.StartUpPosition = 0
.Top = X + 10
.Left = Y + 10
.Show
End With
With Label1
If X < .Left Or X > (.Left + .Width) Or Y > (.Top + .Height) Or Y < .Top Then closeee
End With
End If
End Sub
My code on the second userform
Private Sub UserForm_Activate()
Application.OnTime Now + TimeValue("00:00:03"), "closeee"
End Sub
Private Sub UserForm_Terminate()
On Error Resume Next
With Me
clearallcontrols
End With
Application.OnTime Now + TimeValue("00:00:03"), "closeee", , False
End Sub
Here is a picture of MAin userform when the Info Form is loaded.
Regards,
M

You don't need a timing ... if you want to work with mouse moves, the code to close the info display form (I suppose its name is CurrentJob) should be fired by a UserForm_MouseMove event on the main form, as when leaving the label, the mouse will next be over the form itself (unless you position labels next to each other without any space - which will make the next comment appear as it should).
Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
CurrentJob.Hide
End Sub
I also recommend to pack the info display code in a private sub of its own to keep the code for the various labels clean.
example: I have a form with Label1, Label2, Label3, Textbox1 and following code:
Private Sub ShowInfo(InfoText As String)
' code to query info and show in seperate window
' make sure window doesn't get focus
' I prefer to use non editable text boxes in my main window
Me.TextBox1 = InfoText
End Sub
Private Sub Label1_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
ShowInfo "Mouse is over Label1"
End Sub
Private Sub Label2_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
ShowInfo "Mouse is over Label2"
End Sub
Private Sub Label3_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
ShowInfo "Mouse is over Label3"
End Sub
Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
' this is the exit code
' as here we left all labels
ShowInfo "Mouse is not on a label"
End Sub

Here is the Answer I got on another forum (MrExcel). All the credits go to Jaafar Tribak:
1- Code in a Standard module:
Option Explicit
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 VBA7 Then
#If Win64 Then
Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongPtr, ppacc As Any, pvarChild As Variant) As Long
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 IAccessible, pvarChild As Variant) As Long
Private Declare PtrSafe Function PtInRect Lib "user32" (lpRect As RECT, ByVal x As Long, ByVal y As Long) As Long
#End If
Private Declare PtrSafe Function WindowFromAccessibleObject Lib "oleacc" (ByVal pacc As IAccessible, phwnd 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 Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
Private Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
#Else
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 x As Long, ByVal y As Long) As Long
Private Declare Function WindowFromAccessibleObject Lib "oleacc" (ByVal pacc As IAccessible, phwnd 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 Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
#End If
Private tCursPos As POINTAPI, tControlRect As RECT
Private bFlag As Boolean
Public Function EnableMouseLeaveEevent(ByVal MainUserForm As UserForm, ByVal Ctrl As Control, ByVal TargetUserForm As Object, Optional ByVal TimeOutInSeconds As Long) As Boolean
Dim oIA As IAccessible
Dim w As Long, h As Long
TargetUserForm.StartUpPosition = 0 '<=== (for testing only .. edit out this line if required)
If bFlag = False Then EnableMouseLeaveEevent = True
Ctrl.Tag = IIf(TimeOutInSeconds > 0, ObjPtr(TargetUserForm) & "*" & TimeOutInSeconds & "*" & Timer, ObjPtr(TargetUserForm))
GetCursorPos tCursPos
#If VBA7 Then
Dim Formhwnd As LongPtr
#If Win64 Then
Dim lngPtr As LongPtr
CopyMemory lngPtr, tCursPos, LenB(tCursPos)
Call AccessibleObjectFromPoint(lngPtr, oIA, 0)
#Else
Call AccessibleObjectFromPoint(tCursPos.x, tCursPos.y, oIA, 0)
#End If
#Else
Dim Formhwnd As Long
Call AccessibleObjectFromPoint(tCursPos.x, tCursPos.y, oIA, 0)
#End If
WindowFromAccessibleObject MainUserForm, Formhwnd
With tControlRect
oIA.accLocation .Left, .Top, w, h, 0&
.Right = w + .Left
.Bottom = h + .Top
End With
SetTimer Formhwnd, CLng(ObjPtr(Ctrl)), 0, AddressOf TimerProc
End Function
Private Sub TimerProc(ByVal hwnd As Long, ByVal MSG As Long, ByVal nIDEvent As Long, ByVal dwTimer As Long)
Static tPrevCurPos As POINTAPI
Dim tCurrCurPos As POINTAPI
Dim sArray() As String
Dim oCtrolObj As Object, oTargetFormObj As Object
Dim lTimeOut As Long, lStartTimer As Long
CopyMemory oCtrolObj, nIDEvent, LenB(nIDEvent)
sArray = Split(oCtrolObj.Tag, "*")
CopyMemory oTargetFormObj, CLng(sArray(0)), LenB(nIDEvent)
If UBound(sArray) = 2 Then
lTimeOut = CLng(sArray(1))
lStartTimer = CLng(sArray(2))
End If
GetCursorPos tCurrCurPos
#If VBA7 Then
Dim lngPtr As LongPtr
#If Win64 Then
CopyMemory lngPtr, tCurrCurPos, LenB(tCurrCurPos)
If PtInRect(tControlRect, lngPtr) = 0 Then
#Else
If PtInRect(tControlRect, tCurrCurPos.x, tCurrCurPos.y) = 0 Then
#End If
#Else
Dim lngPtr As Long
If PtInRect(tControlRect, tCurrCurPos.x, tCurrCurPos.y) = 0 Then
#End If
bFlag = False
KillTimer hwnd, nIDEvent
Unload oTargetFormObj
Debug.Print "Mouse Cursor outside button!"
GoTo Xit
Else
If lTimeOut > 0 Then
With tCurrCurPos
If .x = tPrevCurPos.x And .y = tPrevCurPos.y Then
If Timer - lStartTimer > lTimeOut Then
bFlag = True
lStartTimer = Timer
KillTimer hwnd, nIDEvent
Unload oTargetFormObj
Debug.Print "TimeOut!"
End If
Else
bFlag = False
oCtrolObj.Tag = IIf(lTimeOut > 0, ObjPtr(oTargetFormObj) & "*" & lTimeOut & "*" & Timer, ObjPtr(oTargetFormObj))
GoTo Xit
End If
End With
End If
End If
Xit:
CopyMemory oCtrolObj, 0, LenB(nIDEvent)
CopyMemory oTargetFormObj, 0, LenB(nIDEvent)
GetCursorPos tPrevCurPos
End Sub
2- Code usage in UserForm Module:
Private Sub CommandButton1_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal x As Single, ByVal y As Single)
If EnableMouseLeaveEevent(MainUserForm:=Me, Ctrl:=Me.CommandButton1, TargetUserForm:=UserForm2, TimeOutInSeconds:=5) Then ' 5 Sec timeout
UserForm2.Show
End If
End Sub
Thats was a perfect answer.
Links:
VBA- how to have a secondary userform behaviours just like controltiptext
Also a
Demo Excel File

Related

How to achieve a responsive mouseover effect on Controls in a modeless vba Userform on a large Worksheet

I have the following code, which works perfectly fine on a normal VBA Userform: whenever the mouse hovers anywhere over the label, the color of said label is red, otherwise it's white. This effect is very responsive and makes the label feel very Button-like.
Code of the Userform with 1 label on it:
Dim active As Boolean
Private Sub Label1_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
If active = False Then
Label1.BackColor = RGB(255, 0, 0)
active = True
End If
End Sub
Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
If active = True Then
Label1.BackColor = RGB(255, 255, 255)
active = False
End If
End Sub
If i change the UserForm to be called modeless, from a module like this:
Sub loader()
UserForm1.Show vbModeless
End Sub
The Mouseover effect still works but it becomes very sluggish and unresponsive. It seems like the refreshrate has gone down massively.
Edit: I found out this problem only appears when the Active Worksheet is a big one, which obviously slows everything down a bit. The sheet that gives me headaches has around 1000 rows and 50 columns with many cells containing longer strings. I think the sheet itself is around 1MB of Data. Forumlas are set to manual refresh only. I'm on a Laptop with an i7 8550U and 8GB of ram using Office 32 bit.
My question is:
Is it possible to achieve the behaviour of the modal Userform in the modeless one?
I looked for ways to manipulate the refreshrate of a modeless Userform but couldn't find anything helpful.
An alternative solution would be to make scrolling in the Worksheet possible while the Userform is shown in modal mode.
Another solution might be making the UserForm modal while the mouse is on it and modeless once the mouse leaves a certain area (the UserForm borders). Is that possible?
Solution 1 - recommended
Add the following code to your UserForm:
Option Explicit
#If VBA7 Then
Private Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
#Else
Private Declare Sub Sleep Lib "kernel32" (ByVal lngMilliSeconds As Long)
#End If
Dim m_isOpen As Boolean
Private Sub UserForm_Activate()
m_isOpen = True
Do While m_isOpen
Sleep 15 'this correlates to the "refresh rate" of the mouseover effect,
DoEvents 'sleep 100 leads to sluggish behaviour
Loop
End Sub
Private Sub UserForm_Terminate()
m_isOpen = False
End Sub
The mouseover effect should now be responsive again.
Solution 2
This is an implementation of the last of my proposed solution ideas.
It will make the UserForm automatically go modal while the mouse is inside the area of the UserForm and go modeless once the mouse leaves this zone. Just add this code to a plain UserForm:
Option Explicit
#If VBA7 Then
Private Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As PointAPI) As Long
Private Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Declare PtrSafe Function GetDC Lib "user32" (ByVal hWnd As LongPtr) As LongPtr
Private Declare PtrSafe Function GetDeviceCaps Lib "gdi32" (ByVal hdc As LongPtr, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hWnd As LongPtr, ByVal hdc As LongPtr) As Long
#Else
Private Public Declare Function GetCursorPos Lib "user32" (lpPoint As PointAPI) As Long
Private Public Declare Sub Sleep Lib "kernel32" (ByVal lngMilliSeconds As Long)
Private Declare Function GetDC Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function GetDeviceCaps Lib "Gdi32" (ByVal hDC As Long, ByVal nIndex As Long) As Long
Private Declare Function ReleaseDC Lib "user32" (ByVal hWnd As Long, ByVal hDC As Long) As Long
#End If
Private Const LOGPIXELSX = 88
Private Const LOGPIXELSY = 90
Private Type PointAPI
x As Long
y As Long
End Type
Dim m_modal As Boolean
Dim m_modalityIndicator As Object
Private Function pointsPerPixelX() As Double
Dim hdc As LongPtr 'Used for transforming windows API Mouse-coordinates
hdc = GetDC(0) 'to vba coordinates
pointsPerPixelX = 72 / GetDeviceCaps(hdc, LOGPIXELSX)
ReleaseDC 0, hdc
End Function
Private Function pointsPerPixelY() As Double
Dim hdc As LongPtr 'Used for transforming windows API Mouse-coordinates
hdc = GetDC(0) 'to vba coordinates
pointsPerPixelY = 72 / GetDeviceCaps(hdc, LOGPIXELSY)
ReleaseDC 0, hdc
End Function
Private Function GetX() As Long 'Get current X coordinate of Mouse
Dim n As PointAPI
GetCursorPos n
GetX = n.x
End Function
Private Function GetY() As Long 'Get current y coordinate of Mouse
Dim n As PointAPI
GetCursorPos n
GetY = n.y
End Function
Sub MonitorMouse()
Dim x As Long, y As Long
On Error GoTo userform_closed
Do While True
Sleep 15: DoEvents
x = GetX(): y = GetY()
With Me
If m_modal Then
If x < .left / pointsPerPixelX() Or _
x > (.left + .Width) / pointsPerPixelX() Or _
y < .top / pointsPerPixelY() Or _
y > (.top + .Height) / pointsPerPixelY() Then
.Hide
.show vbModeless
m_modal = False
End If
Else
If x > .left / pointsPerPixelX() And _
x < (.left + .Width) / pointsPerPixelX() And _
y > .top / pointsPerPixelY() And _
y < (.top + .Height) / pointsPerPixelY() Then
.Hide
m_modal = True
.show
Exit Sub
End If
End If
End With
Loop
Exit Sub
userform_closed:
err.Clear: On Error GoTo 0
End Sub
Private Function isFormModeless() As Boolean
On Error GoTo EH
Me.show vbModeless: isFormModeless = True
Exit Function
EH:
isFormModeless = False
End Function
Private Sub UserForm_Activate()
If isFormModeless Then
m_modalityIndicator.Caption = "modeless"
Else
m_modalityIndicator.Caption = "modal"
End If
MonitorMouse
End Sub
Private Sub UserForm_Initialize()
Set m_modalityIndicator = Me.Controls.Add("Forms.Label.1", "ModalityIndicator", True)
With m_modalityIndicator
.left = Me.left
.top = Me.top
.Width = Me.Width
.Height = Me.Height
.Font.size = 36
End With
End Sub

How to: Animation (triple dot) on progress bar during working macro

I have a progress bar, which is showing progress in percentage and on 'animated' rectangle.
I know how to show the progress of the macro based on "marks" in code, that's not the case. Example of code called as that "mark" in code to change the percentage on progress bar:
Sub progress(pctCompl As Long)
Progression.Text.Caption = pctCompl & "% Completed"
Progression.Bar.Width = pctCompl * 2
DoEvents 'update the userform
End Sub
I wonder if it's possible to do additional animation behind "Please wait" on that progress bar - triple dot:1 dot, 1 second pause, 2 dots, 1 second pause, 3 dots, 1 second pause. This is 1 loop for that animation.
I was trying to do something, mostly I was achieving infinite loops or macro doing nothing but that triple dot animation, which was freezing Excel application.
Private Sub UserForm_Activate()
Do Until Progression.Bar.Width = 200
Progression.Text2.Caption = "Please wait."
Progression.Repaint
Application.Wait Now + TimeValue("0:00:01")
Progression.Text2.Caption = "Please wait.."
Progression.Repaint
Application.Wait (Now + TimeValue("0:00:01"))
Progression.Text2.Caption = "Please wait..."
Progression.Repaint
Application.Wait (Now + TimeValue("0:00:01"))
Loop
End Sub
I thought it is good place to ask that kind of questions - is it possible and if yes how to achieve that?
I sometimes have an image that I like to 'animate' on a UserForm as a progress indicator, and I use the Win API timer for that. The code below may be a little 'overkill' for your needs, as image changes need to be triggered either by an event or by Repaint, the latter of which can cause flicker. I believe Labels update as soon as the property value changes. If this is the case then you could leave out the listener class shown below and adjust the code accordingly.
With the above caveat, a skeleton implementation could look like this:
Userform code
Note: my userform has a start button, a stop button and one label, called lblWait.
Option Explicit
Private WithEvents mTimerListener As cTimerListener
Private Sub btnStart_Click()
HandleStartTimer mTimerListener
End Sub
Private Sub btnStop_Click()
HandleStopTimer
End Sub
Private Sub mTimerListener_DotCountIncremented(count As Long)
Me.lblWait = "Please wait" & String(count, ".")
End Sub
Private Sub UserForm_Initialize()
Set mTimerListener = New cTimerListener
End Sub
Class code
Note: I've called this class cTimerListener.
Option Explicit
Public Event DotCountIncremented(count As Long)
Private mDotCount As Long
Public Property Let DotCount(RHS As Long)
mDotCount = RHS
If mDotCount > 3 Then mDotCount = 0
RaiseEvent DotCountIncremented(mDotCount)
DoEvents
End Property
Public Property Get DotCount() As Long
DotCount = mDotCount
End Property
And Module code
Option Explicit
#If VBA7 Then
Private Declare PtrSafe Function SetTimer Lib "user32" ( _
ByVal HWnd As LongPtr, _
ByVal nIDEvent As Long, _
ByVal uElapse As Long, _
ByVal lpTimerFunc As LongPtr) As Long
Private Declare PtrSafe Function KillTimer Lib "user32" ( _
ByVal HWnd As LongPtr, _
ByVal nIDEvent As Long) As Long
#Else
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
#End If
Private mTimerId As Long
Private mTimerListener As cTimerListener
Public Sub HandleStartTimer(timerListener As cTimerListener)
Set mTimerListener = timerListener
#If VBA7 Then
mTimerId = SetTimer(0&, 0&, 0.5 * 1000, AddressOf TimerProc64)
#Else
mTimerId = SetTimer(0&, 0&, 0.5 * 1000, AddressOf TimerProc32)
#End If
End Sub
Public Sub HandleStopTimer()
KillTimer 0&, mTimerId
End Sub
#If VBA7 Then
Private Sub TimerProc64(ByVal HWnd As LongPtr, ByVal uMsg As Long, _
ByVal nIDEvent As Long, ByVal dwTimer As Long)
TimerProc
End Sub
#Else
Private Sub TimerProc32(ByVal HWnd As Long, ByVal uMsg As Long, _
ByVal nIDEvent As Long, ByVal dwTimer As Long)
TimerProc
End Sub
#End If
Private Sub TimerProc()
If Not mTimerListener Is Nothing Then
With mTimerListener
.DotCount = .DotCount + 1
End With
End If
End Sub

Show all ControlTipText's in a UserForm on pressing 'Alt'

I'm trying to add ControlTipText's to all MSForms.Control in all Userforms, that can be displayed.
Once all of them are Added, I want to Show all ControlTipText's on pressing 'Alt', so I can easily edit the Controltips on the Excel-Sheet.
Taking Baby-Steps, I first 'tried' to instantly make the ControlTip Visible when adding the Value to it.
What I have now is:
Dim tips As Worksheet
Set tips = Worksheets("CONTROLTIPS")
Dim i As Integer
Dim ctrl As MSForms.Control
i = 0
For Each ctrl In uf.Controls
ctrl.ControlTipText = tips.Cells(i + 3, 2).Value
' ctrl .... ("TIPTEXT").Visible = True ?!?
i = i + 1
Next ctrl
There is no direct way to show the tooltip of a control. The only way is to simulate the mouse hover using APIs. Here is a very basic example. Feel free to amend it to suit your needs.
Prep:
Create a blank userform
Place a commandbutton on the userform and set it's control tip text to whatever you want.
Logic:
When the ALT key is pressed, move the mouse over the relevant control thereby triggering the control tip text
Code
Paste this code in the userform
Option Explicit
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" _
(ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function GetDeviceCaps Lib "Gdi32" _
(ByVal hDC As Long, ByVal nIndex As Long) As Long
Private Declare Function ReleaseDC Lib "user32" _
(ByVal hwnd As Long, ByVal hDC As Long) As Long
Private Declare Function ClientToScreen Lib "user32" _
(ByVal hwnd As Long, lpPoint As POINTAPI) As Long
Private Declare Function SetCursorPos Lib "user32" _
(ByVal X As Long, ByVal Y As Long) As Long
Private Const Xindex = 88
Private Const Yindex = 90
Private Type POINTAPI
X As Long
Y As Long
End Type
'~~> Trap the Alt key in the keydown eveent
Private Sub CommandButton1_KeyDown(ByVal KeyCode As MSForms.ReturnInteger, ByVal Shift As Integer)
If KeyCode = 18 Then MoveMouseOnTopOf Me, CommandButton1
End Sub
'~~> Simulate mouse hover
Public Sub MoveMouseOnTopOf(frm As Object, ctl As Object)
Dim P As POINTAPI
Dim usrfrmHwnd As Long
Dim hDC As Long
Dim X As Double, Y As Double
hDC = GetDC(0)
X = 72 / GetDeviceCaps(hDC, Xindex)
Y = 72 / GetDeviceCaps(hDC, Yindex)
ReleaseDC 0, hDC
P.X = (ctl.Left + (ctl.Width \ 2)) / X
P.Y = (ctl.Top + (ctl.Height \ 2)) / Y
usrfrmHwnd = FindWindow(vbNullString, frm.Caption)
ClientToScreen usrfrmHwnd, P
SetCursorPos P.X, P.Y
End Sub
You can read and understand about the APIs used above in the AllAPI site.
I want to Show all ControlTipText's on pressing 'Alt'
As far as I can tell, this seems to be the reason for you starting this thread.
The values from control tips are stored in the .ControlTipText function. AFAIK the ALT button will not show all control tips, nor is there a similar alternative. What you CAN do, is show all control tips together with their respective controls in a message box:
Private Sub UserForm_Initialize
Dim ctrl As Control
For Each ctrl In Me.Controls
txt = txt & ctrl.Name & ": " & ctrl.ControlTipText & vbNewLine
Next ctrl
MsgBox txt
End Sub

Looking To Get The Colour Of A Picture In Excel

I have a requirement where I need to get the colour of a picture in one of the cells.
Ideally I would like to do this via a piece of VBA Code, but I would be happy enough with a formula if one exists.
Please see attached screenshot.
In this scenario, I would like one of the following options
Replace Each of the Black Box Pictures with False and Replace the White Box Pictures with True
Have a formula that I could type into Column D which would describe the colour of the Picture.
Any help greatly appreciated.
Thanks,
Mark
Screenshot Of Example
This is a beast since we have to hit up a bunch of windows libraries to get the absolute position of the top-left of a cell, grab the pixel, figure out the color, and dump that back into the workbook.
I just did an "Assign Macro" to a picture in Cell D2 so when I click on it, this will stick that same color in Cell A1. You can monkey around with it to get it to do what you need, but all the necessary junk is here to do it.
#If VBA7 Then
Private Declare PtrSafe Function GetPixel Lib "gdi32" (ByVal hDC As LongPtr, ByVal x As Long, ByVal y As Long) As Long
Private Declare PtrSafe Function GetWindowDC Lib "user32" (ByVal hwnd As LongPtr) As LongPtr
Private Declare PtrSafe Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hDC As Long) As Long
Private Declare PtrSafe Function GetSystemMetrics Lib "user32.dll" (ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetDeviceCaps Lib "gdi32" (ByVal hDC As Long, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetCurrentThreadId Lib "kernel32" () As Long
#Else
Private Declare Function GetPixel Lib "gdi32" (ByVal hDC As Long, ByVal x As Long, ByVal y As Long) As Long
Private Declare Function GetWindowDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hDC As Long) As Long
Private Declare Function GetSystemMetrics Lib "user32.dll" (ByVal nIndex As Long) As Long
Private Declare Function GetDeviceCaps Lib "gdi32" (ByVal hDC As Long, ByVal nIndex As Long) As Long
Private Declare Function GetCurrentThreadId Lib "kernel32" () As Long
#End If
Option Explicit
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Private Type POINTAPI
x As Long
y As Long
End Type
Private Function ScreenDPI(bVert As Boolean) As Long
'in most cases this simply returns 96
Static lDPI&(1), lDC&
If lDPI(0) = 0 Then
lDC = GetDC(0)
lDPI(0) = GetDeviceCaps(lDC, 88&) 'horz
lDPI(1) = GetDeviceCaps(lDC, 90&) 'vert
lDC = ReleaseDC(0, lDC)
End If
ScreenDPI = lDPI(Abs(bVert))
End Function
Private Function PTtoPX(Points As Single, bVert As Boolean) As Long
PTtoPX = Points * ScreenDPI(bVert) / 72
End Function
Private Sub GetRangeRect(ByVal rng As Range, ByRef rc As RECT)
Dim wnd As Window
'requires additional code to verify the range is visible
'etc.
Set wnd = rng.Parent.Parent.Windows(1)
With rng
rc.Left = PTtoPX(.Left * wnd.Zoom / 100, 0) _
+ wnd.PointsToScreenPixelsX(0)
rc.Top = PTtoPX(.Top * wnd.Zoom / 100, 1) _
+ wnd.PointsToScreenPixelsY(0)
rc.Right = PTtoPX(.Width * wnd.Zoom / 100, 0) _
+ rc.Left
rc.Bottom = PTtoPX(.Height * wnd.Zoom / 100, 1) _
+ rc.Top
End With
End Sub
Sub CellColor(cellRange As Range)
Dim lColour As Long
Dim lDC As Variant
lDC = GetWindowDC(0)
'Grab the pixel that we will use to determine the color
Dim rc As RECT
Dim xPos As Integer
Dim yPos As Integer
Call GetRangeRect(cellRange, rc)
xPos = rc.Left
yPos = rc.Top
lColour = GetPixel(lDC, xPos, yPos)
Debug.Print xPos, yPos, lColour
Sheet1.Range("a1").Interior.Color = lColour
End Sub
Sub Picture1_Click()
CellColor Sheet1.Range("D2")
End Sub

Set TabStops on a ListBox control in VBA Excel

I first came onto that post here by Randy Birch about listing clipboard formats. As you can see, he is using Visual Basic 6 and also a .Refresh method on List1 after sending the LB_SETTABSTOPS messages to the WNDPROC handling the window corresponding to his "List1" ListBox
Since the .Refresh method is not available in VBA (and also the .Hwnd, but that is less a problem withing this post by C. PEARSON and Private Declare Function GetFocus Lib "user32" () As Long), I tried to 'mimic' it.
Apparently, the .Refresh method invalidates the whole client area of the ListBox Window, and then sends a WM_PAINT message to the WNDPROC bypassing any other pending messages in message queue, causing an immediate repaint of the update region, which should be the entire visible "List1" ListBox in this particular case.
My config :
Debug.Print Application.Version
Debug.Print Application.VBE.Version
Debug.Print Application.OperatingSystem
#If VBA6 Then
Debug.Print "VBA6 = True"
#Else
Debug.Print "VBA6 = False"
#End If
#If VBA7 Then
Debug.Print "VBA7 = True"
#Else
Debug.Print "VBA7 = False"
#End If
Results in:
16.0
7.01
Windows (32-bit) NT 10.00
VBA6 = True
VBA7 = True
Now my attempt #1 :
Option Explicit
Private Const LB_SETTABSTOPS As Long = &H192
Private Const EM_SETTABSTOPS As Long = &HCB
Private Const RDW_ALLCHILDREN = &H80
Private Const RDW_ERASE = &H4
Private Const RDW_ERASENOW = &H200
Private Const RDW_FRAME = &H400
Private Const RDW_INTERNALPAINT = &H2
Private Const RDW_INVALIDATE = &H1
Private Const RDW_NOCHILDREN = &H40
Private Const RDW_NOERASE = &H20
Private Const RDW_NOFRAME = &H800
Private Const RDW_NOINTERNALPAINT = &H10
Private Const RDW_UPDATENOW = &H100
Private Const RDW_VALIDATE = &H8
Private hWndList1 As Long
Private Type Rect
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
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 PostMessage Lib "user32" Alias "PostMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) 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 GetFocus Lib "user32" () As Long
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
Private Declare PtrSafe Function UpdateWindow Lib "user32" (ByVal hWnd As LongPtr) As Boolean
Private Declare Function VarPtrArray Lib "msvbvm60.dll" Alias "VarPtr" (ByRef lpRect As Rect) As Long
Private Declare Function RedrawWindow Lib "user32" (ByVal hWnd As Long, ByRef lprcUpdate As Rect, ByVal hrgnUpdate As Long, Optional ByVal flags As Integer) As Boolean
Private Declare Function InvalidateRect Lib "user32" (ByVal hWnd As Long, ByRef lpRect As Rect, ByVal bErase As Boolean) As Long
Private Declare Function GetUpdateRect Lib "user32" (ByVal hWnd As Long, ByRef lpRect As Rect, ByVal bErase As Boolean) As Boolean
Private Declare Function GetWindowRect Lib "user32" (ByVal hWnd As Long, ByRef lpRect As Rect) As Boolean
Private Declare Function CreateRectRgnIndirect Lib "gdi32" (ByRef lpRect As Rect) As Long
Private Declare Function GetClientRect Lib "user32" (ByVal hWnd As Long, ByRef lpRect As Rect) As Long
Private Declare Function GetDesktopWindow Lib "user32" () As Long
Private Sub UserForm_Initialize()
Dim ListWindowUpdated As Boolean
Dim ListWindowRedrawn As Boolean
ReDim TabStop(0 To 1) As Long
TabStop(0) = 90
TabStop(1) = 130
With List1
.Clear
.SetFocus
hWndList1 = GetFocus
Call SendMessage(hWndList1, LB_SETTABSTOPS, 0&, ByVal 0&)
Call SendMessage(hWndList1, LB_SETTABSTOPS, 2, TabStop(0))
Dim rectList1 As Rect
Call GetWindowRect(hWndList1, rectList1)
Dim lprcList1 As Long
lprcList1 = VarPtrArray(rectList1)
ListWindowRedrawn = RedrawWindow(hWndList1, rectList1, lprcList1, RDW_INVALIDATE)
ListWindowRedrawn = RedrawWindow(hWndList1, rectList1, 0, RDW_INVALIDATE)
MsgBox "ListWindowRedrawn = " & ListWindowRedrawn & " and RDW_INVALIDATE message sent"
'Call RedrawWindowAny(hWndForm2, vbNull, 1&, RDW_INVALIDATE Or RDW_UPDATENOW Or RDW_ALLCHILDREN)
ListWindowUpdated = UpdateWindow(hWndList1)
MsgBox "ListWindowUpdated = " & ListWindowUpdated
End With
End Sub
My attempt #2 :
Dim ScreenRect As Rect
Dim hClientRect As Long
hClientRect = GetClientRect(hWndList1), ScreenRect)
Dim udtScrDim As Rect
Dim lReturn As Long
Dim hRegion As Long
udtScrDim.Left = 0
udtScrDim.Top = 0
udtScrDim.Right = ScreenRect.Right - ScreenRect.Left
MsgBox "Screen width = " & ScreenRect.Right - ScreenRect.Left
udtScrDim.Bottom = ScreenRect.Bottom - ScreenRect.Top
MsgBox "Screen height = " & ScreenRect.Bottom - ScreenRect.Top
hRegion = CreateRectRgnIndirect(udtScrDim)
If hRegion <> 0 Then
lReturn = RedrawWindow(0, udtScrDim, hRegion, RDW_ERASE Or RDW_FRAME Or RDW_INVALIDATE Or RDW_UPDATENOW Or RDW_INTERNALPAINT Or RDW_ALLCHILDREN)
End If
After many attemps, I still can't get the client area to be updated with the custom tabstop positions. But the attempt #1 above still seems to be the more logical to me. It works fine, no errors, but nothing changes, any item (containing vbTab) in the ListBox won't be affected, even with a later UserForm1.Repaint.
Please help :)
This is not quite an answer but more a workaround :
My understanding of the problem (and of Randy Birch) :
The only explaination is that the VBA Listbox control simply can't deal with LB_SETTABSTOPS messages. Indeed I also tried sending the LB_SETTABSTOPS message later, but it's still ignored. Same thing with the invalidate message and WM_PAINT.
That might be why the Office devs implemented the .ColumnWidth property in VBA Excel which can do exactly the same things that what I was trying to do above.

Resources