Jaafar Tribak
Well-known Member
- Joined
- Dec 5, 2002
- Messages
- 9,796
- Office Version
- 2016
- Platform
- Windows
Hi dear forum.
I am sure you are all familiar with the KeyPress and KeyDown events exposed by userform controls. These events not only allow the user to detect any keys being pressed dynamically, but also give the user the opportunity to discard (block) the key if so desired before it actually reaches the target control.
Excel worksheet cells do not provide such functionality. The closest you have is the Worksheet_Change event which unfortunately fires after the key(s) is/are already pressed and the cell is already changed.
I am posting here a vba solution whose aim is to emulate the MSForms KeyPress\KeyDown events for excel worksheets.
The code is based on the RawInput api ... It is worth noting that legacy WH_KEYBOARD & WH_KEYBOARD_LL hooks do not seem to work in x64 that's why I went the RawInput route.
Since this technique subclasses the excel application, I placed the actual window callback procedure inside a dll (which I developped and compiled in TwinBasic) ... This, plus relying on the help of an intermediary userform is the secret to keeping excel stable while subclassed. Therefore, any unhandled errors or executing the Stop statement and even pressing the Reset, Break or Design mode buttons in the VBE will simply release the hook from memory but won't shut excel down. The Install Method provides an optional NotifyUserUponLossOfState argument in case you want to be notified when a loss of state occurs in the project and the hook is released.
I stored the dlls binary data as base64 string in their own separate modules as resources for better portability. The code automatically takes care of decoding the base64 string, extracting the dll bytes and finally saving them to disk as temporary dll files.
This should work in x32 and x64 bits environements.
File Demo for downloding:
KeyStrokesMonitor_X32_X64.xlsm
The use is super simple as shown in the following demo :
In a bas module:
1- In case anyone is interested and for future reference, here is a the compiled x64 dll in twinbasic:
2- And this is the compiled x32 dll in twinbasic:
Any feedback, suggestions will be appreciated.
Regards.
I am sure you are all familiar with the KeyPress and KeyDown events exposed by userform controls. These events not only allow the user to detect any keys being pressed dynamically, but also give the user the opportunity to discard (block) the key if so desired before it actually reaches the target control.
Excel worksheet cells do not provide such functionality. The closest you have is the Worksheet_Change event which unfortunately fires after the key(s) is/are already pressed and the cell is already changed.
I am posting here a vba solution whose aim is to emulate the MSForms KeyPress\KeyDown events for excel worksheets.
The code is based on the RawInput api ... It is worth noting that legacy WH_KEYBOARD & WH_KEYBOARD_LL hooks do not seem to work in x64 that's why I went the RawInput route.
Since this technique subclasses the excel application, I placed the actual window callback procedure inside a dll (which I developped and compiled in TwinBasic) ... This, plus relying on the help of an intermediary userform is the secret to keeping excel stable while subclassed. Therefore, any unhandled errors or executing the Stop statement and even pressing the Reset, Break or Design mode buttons in the VBE will simply release the hook from memory but won't shut excel down. The Install Method provides an optional NotifyUserUponLossOfState argument in case you want to be notified when a loss of state occurs in the project and the hook is released.
I stored the dlls binary data as base64 string in their own separate modules as resources for better portability. The code automatically takes care of decoding the base64 string, extracting the dll bytes and finally saving them to disk as temporary dll files.
This should work in x32 and x64 bits environements.
File Demo for downloding:
KeyStrokesMonitor_X32_X64.xlsm
The use is super simple as shown in the following demo :
In a bas module:
VBA Code:
Option Explicit
Private KeyPressMonitor As IKeyBoardMonitor
Sub StartMonitoring()
Set KeyPressMonitor = New CKeyBoardMonitor
KeyPressMonitor.Install lpCallbackFunc:=AddressOf OnKeyPress, NotifyUserUponLossOfState:=True
End Sub
Sub FinishMonitoring()
KeyPressMonitor.UnInstall
End Sub
Sub RaiseError()
Debug.Print 1 / 0
End Sub
'______________________________________ Callback Procedure ______________________________________
'Demo:
Public Sub OnKeyPress( _
ByVal KeyCode As Integer, _
ByVal KeyAscii As Integer, _
ByRef bDiscardKey As Boolean _
)
If ActiveWorkbook Is ThisWorkbook Then
If KeyAscii = 97 Then '<== block the 'a' key.
bDiscardKey = True
End If
Debug.Print KeyCode, KeyAscii, bDiscardKey
'Debug.Print 1 / 0
'Stop
End If
End Sub
1- In case anyone is interested and for future reference, here is a the compiled x64 dll in twinbasic:
VBA Code:
Module MainModule
Option Explicit
Private Type POINTAPI
X As Long
Y As Long
End Type
Private Type MSG
hwnd As LongPtr
message As Long
wParam As LongPtr
lParam As LongPtr
time As Long
pt As POINTAPI
End Type
Private Type RAWINPUTDEVICE
usUsagePage As Integer
usUsage As Integer
dwFlags As Long
hWndTarget As LongPtr
End Type
Private Type RAWINPUTHEADER
dwType As Long
dwSize As Long
hDevice As LongPtr
wParam As LongPtr
End Type
Private Type tagRAWKEYBOARD
Header As RAWINPUTHEADER
MakeCode As Integer
Flags As Integer
Reserved As Integer
VKey As Integer
Message As Long
ExtraInformation As Long
End Type
Private Type FmlaInfo
wPointMode As Long
Padding(20&) As Byte
End Type
Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpDst As Any, lpSrc As Any, ByVal ByteLength As LongPtr)
Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As Long
Private Declare PtrSafe Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As LongPtr, ByVal hwnd As LongPtr, ByVal MSG As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
Private Declare PtrSafe Function RegisterRawInputDevices Lib "user32" (pRawInputDevices As RAWINPUTDEVICE, ByVal uiNumDevices As Long, ByVal cbSize As Long) As Long
Private Declare PtrSafe Function GetRawInputData Lib "user32" (ByVal hRawInput As LongPtr, ByVal uiCommand As Long, pData As Any, pCbSize As Long, ByVal cbSizeHeader As Long) As Long
Private Declare PtrSafe Function ToUnicode Lib "user32" (ByVal wVirtKey As Long, ByVal wScanCode As Long, lpKeyState As Byte, ByVal pwszBuff As LongPtr, ByVal cchBuff As Long, ByVal wFlags As Long) As Long
Private Declare PtrSafe Function GetKeyboardState Lib "user32" (pbKeyState As Byte) As Long
Private Declare PtrSafe Function WaitMessage Lib "user32" () 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 PostMessage Lib "user32" Alias "PostMessageA" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As Long
Private Declare PtrSafe Function RegisterHotKey Lib "user32" Alias "RegisterHotKey" (ByVal hwnd As LongPtr, ByVal id As Long, ByVal fsModifiers As Long, ByVal vk As Long) As Long
Private Declare PtrSafe Function UnregisterHotKey Lib "user32" Alias "UnregisterHotKey" (ByVal hwnd As LongPtr, ByVal id As Long) As Long
Private Declare PtrSafe Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
Private Declare PtrSafe Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
Private Declare PtrSafe Function LPenHelper Lib "XLCALL32.DLL" (ByVal wCode As Long, fmlaInfo As FmlaInfo) As Long
Private Declare PtrSafe Function GetActiveWindow Lib "user32" Alias "GetActiveWindow" () As LongPtr
Private Declare PtrSafe Function IsWindow Lib "user32" Alias "IsWindow" (ByVal hwnd As LongPtr) As Long
Private Const GWL_WNDPROC = (-4&), RIDEV_INPUTSINK = &H100, RIDEV_REMOVE = &H1&
Private tRawInput As RAWINPUTDEVICE
Private hInputWind As LongPtr, lPrvWndProc As LongPtr, hApp As LongPtr, oInterface As Object
Private hForm As LongPtr, bNotifyUser As Boolean
[DllExport]
Public Sub InstallHook(ByVal ptr As LongPtr, ByVal hParentHwnd As LongPtr, ByVal hFormWnd As LongPtr, ByVal NotifyUserUponLossOfState As Boolean)
Const VK_ESCAPE= &H1B
hForm = hFormWnd: bNotifyUser = NotifyUserUponLossOfState
If GetProp(hForm, "Subclassed") <> -1 Then
hApp = hParentHwnd
Call RegisterHotKey(hApp, 1&, 0&, VK_ESCAPE)
Call InstallKeyboardHook(hApp)
Call CopyMemory(oInterface, ptr, 8^)
End If
End Sub
[DllExport]
Public Sub RemoveHooK()
If GetProp(hApp, "Subclassed") = -1 Then
RemoveProp hApp, "Subclassed"
Call CopyMemory(oInterface, 0, 8^)
Call UnregisterHotKey(hApp, 1&)
tRawInput.dwFlags = RIDEV_REMOVE
tRawInput.hWndTarget = hInputWind
Call RegisterRawInputDevices(tRawInput, 1, LenB(tRawInput))
Call SetWindowLong(hInputWind, GWL_WNDPROC, lPrvWndProc)
End If
End Sub
Private Sub InstallKeyboardHook(ByVal hwnd As LongPtr)
Const HID_USAGE_PAGE_GENERIC = &H1, HID_USAGE_GENERIC_KEYBOARD = &H6, WS_CHILD = &H40000000
hInputWind = hwnd
lPrvWndProc = SetWindowLong(hInputWind, GWL_WNDPROC, AddressOf WindowProc)
With tRawInput
.usUsagePage = HID_USAGE_PAGE_GENERIC
.usUsage = HID_USAGE_GENERIC_KEYBOARD
.dwFlags = RIDEV_INPUTSINK
.hWndTarget = hInputWind
End With
Call RegisterRawInputDevices(tRawInput, 1, LenB(tRawInput))
End Sub
Private Function WindowProc( _
ByVal hwnd As LongPtr, _
ByVal wMsg As Long, _
ByVal wParam As LongPtr, _
ByVal lParam As LongPtr _
) As LongPtr
Const WM_INPUT = &HFF, WM_DESTROY = &H2, WM_KEYDOWN = &H100
Const RID_INPUT = &H10000003, RIM_TYPEKEYBOARD = 1
Const PM_REMOVE = &H1, VK_ESCAPE= &H1B, VK_DELETE = &H2E
Dim tRaw As tagRAWKEYBOARD
Dim tMsg As MSG
Dim pCbSize As Long
Dim bDataBuff() As Byte
Dim bKeyState(0 To 255) As Byte
Dim sBuffer As String
Dim bDiscardKey As Boolean
On Error Resume Next
If IsWindow(hForm) = 0 Then
Call RemoveHooK
If GetProp(hApp, "CLOSING") <> -1 Then
Call NotifyUser
End If
End If
Select Case wMsg
Case WM_DESTROY
If GetProp(hApp, "CLOSING") <> -1 Then
Call NotifyUser
End If
Call RemoveHooK
Case WM_INPUT
Call GetRawInputData(lParam, RID_INPUT, ByVal 0&, pCbSize, Len(tRaw.Header))
If pCbSize >= Len(tRaw) Then
ReDim bDataBuff(0 To pCbSize) As Byte
Call GetRawInputData(lParam, RID_INPUT, bDataBuff(0), pCbSize, Len(tRaw.Header))
Call CopyMemory(tRaw, bDataBuff(0), Len(tRaw))
End If
If hApp <> GetActiveWindow Then Exit Function
If tRaw.VKey = VK_DELETE Or tRaw.VKey = VK_ESCAPE Then Exit Function
Call WaitMessage
If tRaw.Header.dwType = RIM_TYPEKEYBOARD And tRaw.Message = WM_KEYDOWN Then
Call GetKeyboardState(bKeyState(0))
sBuffer = String(64, vbNullChar)
If ToUnicode(tRaw.VKey, tRaw.MakeCode, bKeyState(0), StrPtr(sBuffer), Len(sBuffer) - 1, 0) > 0 Then
sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
Call PeekMessage(tMsg, 0^, WM_KEYDOWN, WM_KEYDOWN, PM_REMOVE)
If IsEditMode Then
Call UnregisterHotKey(hApp, 1&)
Else
Call RegisterHotKey(hApp, 1&, 0&, VK_ESCAPE)
End If
oInterface.EventRaiser(ByVal tRaw.VKey, ByVal AscW(sBuffer), bDiscardKey)
If bDiscardKey = False Then
PostMessage tMsg.hwnd, tMsg.message, tMsg.wParam, tMsg.lParam
WindowProc = -1^
Exit Function
End If
End If
End If
End Select
WindowProc = CallWindowProc(lPrvWndProc, hwnd, wMsg, wParam, lParam)
End Function
Private Function IsEditMode() As Boolean
Const xlModeReady = 0&, xlSpecial = &H4000, xlGetFmlaInfo = (14& Or xlSpecial)
Dim tFInfo As FmlaInfo
Call LPenHelper(xlGetFmlaInfo, tFInfo)
If tFInfo.wPointMode <> xlModeReady Then
IsEditMode = True
End If
End Function
Private Sub NotifyUser()
If bNotifyUser Then
MsgBox "[ Error! ]" & vbNewLine & _
"The KeyMonitor Project was released from memory." _
& vbNewLine & vbNewLine & "The KeyMonitor is no longer in operation." _
& vbNewLine & "Please, try installing it again.", vbMsgBoxSetForeground Or vbExclamation Or vbApplicationModal
End If
End Sub
End Module
2- And this is the compiled x32 dll in twinbasic:
VBA Code:
Module MainModule
Option Explicit
Private Type POINTAPI
X As Long
Y As Long
End Type
Private Type MSG
hwnd As Long
message As Long
wParam As Long
lParam As Long
time As Long
pt As POINTAPI
End Type
Private Type RAWINPUTDEVICE
usUsagePage As Integer
usUsage As Integer
dwFlags As Long
hWndTarget As Long
End Type
Private Type RAWINPUTHEADER
dwType As Long
dwSize As Long
hDevice As Long
wParam As Long
End Type
Private Type tagRAWKEYBOARD
Header As RAWINPUTHEADER
MakeCode As Integer
Flags As Integer
Reserved As Integer
VKey As Integer
Message As Long
ExtraInformation As Long
End Type
Private Type FmlaInfo
wPointMode As Long
Padding(20&) As Byte
End Type
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpDst As Any, lpSrc As Any, ByVal ByteLength As Long)
Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare Function RegisterRawInputDevices Lib "user32" (pRawInputDevices As RAWINPUTDEVICE, ByVal uiNumDevices As Long, ByVal cbSize As Long) As Long
Private Declare Function GetRawInputData Lib "user32" (ByVal hRawInput As Long, ByVal uiCommand As Long, pData As Any, pCbSize As Long, ByVal cbSizeHeader As Long) As Long
Private Declare Function ToUnicode Lib "user32" (ByVal wVirtKey As Long, ByVal wScanCode As Long, lpKeyState As Byte, ByVal pwszBuff As Long, ByVal cchBuff As Long, ByVal wFlags As Long) As Long
Private Declare Function GetKeyboardState Lib "user32" (pbKeyState As Byte) As Long
Private Declare Function CreateWindowEx Lib "user32" Alias "CreateWindowExA" (ByVal dwExStyle As Long, ByVal lpClassName As String, ByVal lpWindowName As String, ByVal dwStyle As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hWndParent As Long, ByVal hMenu As Long, ByVal hInstance As Long, lpParam As Any) As Long
Private Declare Function DestroyWindow Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hwnd As Long, ByVal MSG As Long, ByVal wParam As Long, ByVal lParam 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 PostMessage Lib "user32" Alias "PostMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function RegisterHotKey Lib "user32" (ByVal hwnd As Long, ByVal id As Long, ByVal fsModifiers As Long, ByVal vk As Long) As Long
Private Declare Function UnregisterHotKey Lib "user32" (ByVal hwnd As Long, ByVal id As Long) As Long
Private Declare Function GetNextWindow Lib "user32" Alias "GetWindow" (ByVal hwnd As Long, ByVal wFlag As Long) As Long
Private Declare Function LPenHelper Lib "XLCALL32.DLL" (ByVal wCode As Long, fmlaInfo As FmlaInfo) As Long
Private Declare Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As Long, ByVal lpString As String, ByVal hData As Long) As Long
Private Declare Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Private Declare Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Private Declare Function GetActiveWindow Lib "user32" Alias "GetActiveWindow" () As Long
Private Const GWL_WNDPROC = (-4&), RIDEV_INPUTSINK = &H100, RIDEV_REMOVE = &H1&
Private tRawInput As RAWINPUTDEVICE
Private hInputWind As Long, lPrvWndProc As Long, hApp As Long, oInterface As Object
Private hForm As Long, bNotifyUser As Boolean
[DllExport]
Public Sub InstallHook(ByVal ptr As Long, ByVal hParentHwnd As Long, ByVal NotifyUserUponLossOfState As Boolean)
Const GW_OWNER = 4, VK_ESCAPE= &H1B
hForm = hParentHwnd: bNotifyUser = NotifyUserUponLossOfState
If GetProp(hForm, "Subclassed") <> -1& Then
hApp = hParentHwnd
hApp = GetNextWindow(hApp, GW_OWNER)
Call RegisterHotKey(hApp, 1&, 0&, VK_ESCAPE)
Call InstallKeyboardHook(hParentHwnd)
Call CopyMemory(oInterface, ptr, 4)
End If
End Sub
[DllExport]
Public Sub RemoveHooK()
If GetProp(hForm, "Subclassed") = -1& Then
RemoveProp hForm, "Subclassed"
Call CopyMemory(oInterface, 0, 4)
Call UnregisterHotKey(hApp, 1&)
tRawInput.dwFlags = RIDEV_REMOVE
tRawInput.hWndTarget = hInputWind
Call RegisterRawInputDevices(tRawInput, 1, LenB(tRawInput))
Call SetWindowLong(hInputWind, GWL_WNDPROC, lPrvWndProc)
DestroyWindow hInputWind
End If
End Sub
Private Sub InstallKeyboardHook(ByVal hwnd As Long)
Const HID_USAGE_PAGE_GENERIC = &H1, HID_USAGE_GENERIC_KEYBOARD = &H6, WS_CHILD = &H40000000
hInputWind = CreateWindowEx(0&, "Static", vbNullString, WS_CHILD, 0&, 0&, 0&, 0&, hwnd, 0&, 0&, 0&)
lPrvWndProc = SetWindowLong(hInputWind, GWL_WNDPROC, AddressOf WindowProc)
With tRawInput
.usUsagePage = HID_USAGE_PAGE_GENERIC
.usUsage = HID_USAGE_GENERIC_KEYBOARD
.dwFlags = RIDEV_INPUTSINK
.hWndTarget = hInputWind
End With
Call RegisterRawInputDevices(tRawInput, 1, LenB(tRawInput))
End Sub
Private Function WindowProc( _
ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
ByVal lParam As Long _
) As Long
Const WM_INPUT = &HFF, WM_DESTROY = &H2, WM_KEYDOWN = &H100
Const RID_INPUT = &H10000003, RIM_TYPEKEYBOARD = 1
Const PM_REMOVE = &H1, VK_ESCAPE= &H1B, VK_DELETE = &H2E
Dim tRaw As tagRAWKEYBOARD
Dim tMsg As MSG
Dim pCbSize As Long
Dim bDataBuff() As Byte
Dim bKeyState(0 To 255) As Byte
Dim sBuffer As String
Dim bDiscardKey As Boolean
On Error Resume Next
Select Case wMsg
Case WM_DESTROY
If GetProp(hApp, "CLOSING") <> -1& Then
Call NotifyUser
End If
Call RemoveHooK
Call SetWindowLong(hwnd, GWL_WNDPROC, lPrvWndProc)
Case WM_INPUT
Call GetRawInputData(lParam, RID_INPUT, ByVal 0&, pCbSize, Len(tRaw.Header))
If pCbSize >= Len(tRaw) Then
ReDim bDataBuff(0 To pCbSize) As Byte
Call GetRawInputData(lParam, RID_INPUT, bDataBuff(0), pCbSize, Len(tRaw.Header))
Call CopyMemory(tRaw, bDataBuff(0), Len(tRaw))
End If
If hApp <> GetActiveWindow Then Exit Function
If tRaw.VKey = VK_DELETE Or tRaw.VKey = VK_ESCAPE Then Exit Function
Call WaitMessage
If tRaw.Header.dwType = RIM_TYPEKEYBOARD And tRaw.Message = WM_KEYDOWN Then
Call GetKeyboardState(bKeyState(0))
sBuffer = String(64, vbNullChar)
If ToUnicode(tRaw.VKey, tRaw.MakeCode, bKeyState(0), StrPtr(sBuffer), Len(sBuffer) - 1, 0) > 0 Then
sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
Call PeekMessage(tMsg, 0, WM_KEYDOWN, WM_KEYDOWN, PM_REMOVE)
If IsEditMode Then
Call UnregisterHotKey(hApp, 1&)
Else
Call RegisterHotKey(hApp, 1&, 0&, VK_ESCAPE)
End If
oInterface.EventRaiser(ByVal tRaw.VKey, ByVal AscW(sBuffer), bDiscardKey)
If bDiscardKey = False Then
PostMessage tMsg.hwnd, tMsg.message, tMsg.wParam, tMsg.lParam
WindowProc = -1
Exit Function
End If
End If
End If
End Select
WindowProc = CallWindowProc(lPrvWndProc, hwnd, wMsg, wParam, lParam)
End Function
Private Function IsEditMode() As Boolean
Const xlModeReady = 0&, xlSpecial = &H4000, xlGetFmlaInfo = (14& Or xlSpecial)
Dim tFInfo As FmlaInfo
Call LPenHelper(xlGetFmlaInfo, tFInfo)
If tFInfo.wPointMode <> xlModeReady Then
IsEditMode = True
End If
End Function
Private Sub NotifyUser()
If bNotifyUser Then
MsgBox "[ Error! ]" & vbNewLine & _
"The KeyMonitor Project was released from memory." _
& vbNewLine & vbNewLine & "The KeyMonitor is no longer in operation." _
& vbNewLine & "Please, try installing it again.", vbMsgBoxSetForeground Or vbExclamation Or vbApplicationModal
End If
End Sub
End Module
Any feedback, suggestions will be appreciated.
Regards.
Last edited: