-
Sep 13th, 2024, 02:13 AM
#1
Thread Starter
Hyperactive Member
RawInput
Hi,
I have registered a message only window with RegisterRawInputDevices to monitor keyboard input. The code works well for monitoring key strokes via the GetRawInputData api but, is there a way to block only some specific key(s) ? (not the entire keyboard)
I know this can be done with subclassing and legacy keyboard windows hooks but can it be done with RawInput ?
Thanks.
-
Sep 13th, 2024, 03:12 PM
#2
Thread Starter
Hyperactive Member
-
Sep 14th, 2024, 11:40 PM
#3
Thread Starter
Hyperactive Member
Re: RawInput
Below is the code I have for anyone willing to carry out a quick test ... When the InstallHook SUB is ran, all key strokes are monitored in the window procedure and sent to the debug window. I am just unable to figure out how to block the character "A" and prevent it from reaching the application.
Anyone ?
Code:
Option Explicit
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 Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (lpDst As Any, lpSrc As Any, ByVal ByteLength 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 SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong 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 hWind As Long, lPrvWndProc As Long
Sub InstallHook()
Call InstallKeyboardHook(bInstall:=True)
End Sub
Sub RemoveHook()
Call InstallKeyboardHook(bInstall:=False)
End Sub
Sub InstallKeyboardHook(Optional ByVal bInstall As Boolean = True)
Const GWL_WNDPROC = (-4&), HWND_MESSAGE As Long = (-3&), RIDEV_INPUTSINK = &H100, RIDEV_REMOVE = &H1&
Const HID_USAGE_PAGE_GENERIC = &H1, HID_USAGE_GENERIC_KEYBOARD = &H6
Dim tRawInput As RAWINPUTDEVICE
If bInstall Then
hWind = CreateWindowEx(0&, "Static", vbNullString, 0&, 0&, 0&, 0&, 0&, HWND_MESSAGE, 0&, 0&, 0&)
lPrvWndProc = SetWindowLong(hWind, GWL_WNDPROC, AddressOf WindowProc)
Else
Call DestroyWindow(hWind)
End If
With tRawInput
.usUsagePage = HID_USAGE_PAGE_GENERIC
.usUsage = HID_USAGE_GENERIC_KEYBOARD
.dwFlags = IIf(bInstall, RIDEV_INPUTSINK, RIDEV_REMOVE)
.hWndTarget = hWind
End With
Call RegisterRawInputDevices(tRawInput, 1, LenB(tRawInput))
End Sub
Function WindowProc( _
ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
ByVal lParam As Long _
) As Long
Const WM_INPUT = &HFF, RID_INPUT = &H10000003, RIM_TYPEKEYBOARD = 1, WM_KEYDOWN = &H100
Dim pCbSize As Long
Dim tRaw As tagRAWKEYBOARD
Dim bDataBuff() As Byte
Dim bKeyState(0 To 255) As Byte
Dim sBuffer As String
Select Case wMsg
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 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)
If sBuffer = "A" Then
'BLOCK character "A" '<========== not working. How to ??
Else
Debug.Print sBuffer
End If
End If
End If
End Select
WindowProc = CallWindowProc(lPrvWndProc, hwnd, wMsg, wParam, lParam)
End Function
Last edited by AngelV; Sep 14th, 2024 at 11:43 PM.
-
Sep 15th, 2024, 01:08 AM
#4
Re: RawInput
I really don't think there's a way to block it at that point. Nothing in the documentation or examples I've found suggests it's possible. The system already received it and likely sent it to other windows before yours. You need something built for purpose like SetWindowsHookEx, registering a hotkey then dropping it, or a driver.
Last edited by fafalone; Sep 15th, 2024 at 01:12 AM.
-
Sep 16th, 2024, 04:48 AM
#5
Thread Starter
Hyperactive Member
Re: RawInput
Thanks.
I have found a workaround. I am now using RIDEV_NOLEGACY instead of the RIDEV_INPUTSINK flag. That flag blocks all keyboard input, then I just use the SendInput api except for the character(s) that I want to keep blocked.
-
Sep 16th, 2024, 06:59 AM
#6
Re: RawInput
What's the advantage of this method over let's say the "KeyPreview" property of the form or even handling WM_CHAR if you're going to subcass the form anyway?
-
Sep 16th, 2024, 05:41 PM
#7
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
What's the advantage of this method over let's say the "KeyPreview" property of the form or even handling WM_CHAR if you're going to subcass the form anyway?
Because I was planning to use this code in offce vba. Furthermore, RawInput seems slightly more stable in office (at least in my testings so far) than trapping the WM_CHAR msg or using legacy WH_KEYBOARD\WH_KEYBOARD_LL hooks.
-
Sep 16th, 2024, 07:13 PM
#8
Re: RawInput
Probably you could use TwinBasic to compile a 64bit ActiveX DLL for subclassing that would make it a lot safer for handling WM_CHAR and other messages you'd like to process without crashing. Sounds better than blocking everything with RawInput and sending keys back with SendInput...
-
Sep 16th, 2024, 08:25 PM
#9
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
Probably you could use TwinBasic to compile a 64bit ActiveX DLL for subclassing that would make it a lot safer for handling WM_CHAR and other messages you'd like to process without crashing. Sounds better than blocking everything with RawInput and sending keys back with SendInput...
Never used twinbasic. I hear it is good.
I have a couple of questions:
1- Can twinbasic make standard dlls (as opposed to ActiveX) ?
2- Does that include support for x32bit and x64bit dlls ?
3- If so, I am envisioning writing a small std dll with twbasic that can be loaded into the Excel process. The dll will simply subclass the main excel window to trap window messages or instead of subclassing, it will install a keyboard hook to monitor keystrokes directed to Excel. My question is: Will unhandled errors crash Excel while excel is subclassed or while a keybaord hook is installed ? As we know, in debug mode, callback unhandled errors (or pressing the IDE Stop button) cause office/vba applications to crash. Will placing the callback in the loaded dll prevent crashing Excel ? I don't think so.
-
Sep 16th, 2024, 08:37 PM
#10
Re: RawInput
The reason I suggested an ActiveX DLL is because, beside placing the callback inside, it can raise events back to your VBA application and those won't crash on Stop. At least that's what I did with my VB6 Subclassing DLL and it's been smooth sailing ever since. The code is fairly simple so I thought it could be ported to 64bit and TwinBasic should be the right tool for it.
-
Sep 16th, 2024, 10:22 PM
#11
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
The reason I suggested an ActiveX DLL is because, beside placing the callback inside, it can raise events back to your VBA application and those won't crash on Stop. At least that's what I did with my VB6 Subclassing DLL and it's been smooth sailing ever since. The code is fairly simple so I thought it could be ported to 64bit and TwinBasic should be the right tool for it.
Nice subclassing dll. Thanks.
I see the point of chosing ActiveX over Std dll for raising events back to the Class client, the COM way ... I just prefer not to have to go through ActiveX registration and then having to reference the ActiveX in the vba project @ design time.
-
Sep 17th, 2024, 05:35 PM
#12
Re: RawInput
Originally Posted by VanGoghGaming
The reason I suggested an ActiveX DLL is because, beside placing the callback inside, it can raise events back to your VBA application and those won't crash on Stop. At least that's what I did with my VB6 Subclassing DLL and it's been smooth sailing ever since. The code is fairly simple so I thought it could be ported to 64bit and TwinBasic should be the right tool for it.
Nearly all my tB projects have all that comctl32 subclassing code ported already, just need to copy and paste over the function prototypes and API defs.
-
Sep 17th, 2024, 11:24 PM
#13
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
The reason I suggested an ActiveX DLL is because, beside placing the callback inside, it can raise events back to your VBA application and those won't crash on Stop. At least that's what I did with my VB6 Subclassing DLL and it's been smooth sailing ever since. The code is fairly simple so I thought it could be ported to 64bit and TwinBasic should be the right tool for it.
Hi VanGoghGaming,
I have compiled your cSC.cls code into prjSafeSubclassing_win32.dll (x32bit build) in twinbasic.
When I use the compiled ActiveX dll in excel x32bit, it works as expected BUT the form crashes when unloaded w/o warning. It also crashes when executing Debug.Print 1 \ 0 in the callback.
I have added a MsgBox for testing in the cSc Class Class_Terminate event, but the MsgBox never shows up indicating that the class terminate event is never called when unloading the client form. I thought the cSc class terminate event would fire automatically when closing the calling client form but that doesn't seem to be the case.
Any idea what may be the cause ? This is the first time I use twinbasic, so maybe I am missing something.
EDIT:
Forget about the crashing problem. I had forgotten to set the Subclass variable to Nothing upon unloading the form so it is now firing the cSc class Terminate event and it is no longer crashing excel when closing the client form. (BTW, I see that you didn't explicitly set the Subclass object variable to Nothing in your Form code ! how is that?)
This is what I did to prevent the crashing
Code:
Private Sub UserForm_Terminate()
Set Subclass = Nothing
End Sub
However, Debug.Print 1 \ 0 in the callback still crashes the excel application and keeps bringing up the following error dialog repeatedly and I can't come out of it, hence crashing the entire application:
Last edited by AngelV; Sep 17th, 2024 at 11:56 PM.
-
Sep 18th, 2024, 07:38 AM
#14
Re: RawInput
For 32bit you could just use VB6, I suggested TwinBasic only for a 64bit variant. I have not experienced the need to explicitly set objects to Nothing as VB6 does that automatically when they go out of scope.
Unfortunately I don't have Microsoft Office so I can't test it in VBA but from what you're saying it seems the behavior is different than VB6 in this regard. The VB6 IDE continues to execute binary code from ActiveX DLLs even when the project is terminated prematurely with Stop/End.
It's still weird that you needed to manually set it to Nothing since even in VBA the form should receive the WM_NCDESTROY message when being closed normally and that should also trigger clean unsubclassing...
-
Sep 18th, 2024, 07:45 AM
#15
Re: RawInput
In Excel VBA there are no compiled binaries I assume, everything is ran from the IDE
-
Sep 18th, 2024, 07:56 AM
#16
Re: RawInput
The discussion is about an ActiveX DLL which is very much compiled (by VB6 or TwinBasic or another programming language). I assume Excel can also instantiate objects from such ActiveX DLLs.
-
Sep 18th, 2024, 01:05 PM
#17
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
For 32bit you could just use VB6, I suggested TwinBasic only for a 64bit variant. I have not experienced the need to explicitly set objects to Nothing as VB6 does that automatically when they go out of scope.
I don't have VB6 so I need the twinbasic compiler even for x32 builds.
Unfortunately I don't have Microsoft Office so I can't test it in VBA but from what you're saying it seems the behavior is different than VB6 in this regard. The VB6 IDE continues to execute binary code from ActiveX DLLs even when the project is terminated prematurely with Stop/End.
Yes. In theory, the VB6 IDE and the VBA Editor should be similar in that respect since the callback in the dll remains running in memory when the error occurs. Unfortunatly, I keep getting that nasty shutdown error.
It's still weird that you needed to manually set it to Nothing since even in VBA the form should receive the WM_NCDESTROY message when being closed normally and that should also trigger clean unsubclassing...
The VBA form does receive the WM_NCDESTROY. I have added msgbox in the WndProc for testing as follows and the Msgbox does show up.
Code:
Select Case uMsg
Case WM_NCDESTROY ' Remove subclassing as the window is about to be destroyed
Subclass.UnSubclassWnd hwnd
MsgBox "msgbox called -- form should be unsubclassed at this point."
It is the class Terminate Event that doesn't fire unless the variable holding the activeX class instance is explicitly set to Nothing !
Note: This behaviour doesn't normally occur when instanciating normal classes in vba forms. ie:= When a vba form makes use of a normal user defined class residing in a vba project, the class instance is automatically released when closing the form. This is the expected logical behaviour but for some reason, the ActiveX class is not released unless it is explicitly set to Nothing before unloading the form. Strange!
EDIT:
If I add On Error Resume Next at the start of the WndProc, Debug.Print 1/0 doesn't raise the error but that's cheating and bad coding, plus it hides potential issues. Furthermore, compile errors still crash the application.
Last edited by AngelV; Sep 18th, 2024 at 01:11 PM.
-
Sep 18th, 2024, 02:05 PM
#18
Re: RawInput
In VB6, when the "Debug.Print 1 \ 0" line is executed in the event procedure, I get the following prompt:
Then I can just click "Debug" and skip over the offending line (yellow colored) in the debugger and then execution can resume normally (F5). Clicking "End" also works fine.
Doesn't this debugging feature work in Excel VBA? This is very strange indeed...
-
Sep 18th, 2024, 02:15 PM
#19
Re: RawInput
VBA UserForms and VB6 forms are very different animals, and VBA does a lot of weird stuff underneath VB6 doesn't or does differently; 64bit is worse.
Remember they're both a major and minor revision apart; they didn't add features beyond PtrSafe/LongPtr and LongLong (the latter in 64bit only), but there were probably substantial internals changes. With 64bit I expect they felt free to ignore compatibility with "undocumented" features like everything related to AddressOf and the *Ptr functions.
-
Sep 18th, 2024, 03:06 PM
#20
Re: RawInput
Be that as it may, I don't see a reason why VBA shouldn't be able to debug an event procedure (while preventing more events from coming in debug mode) the same as VB6. Unless TwinBasic implemented the WithEvents/RaiseEvent pair in a radically different manner.
-
Sep 18th, 2024, 03:15 PM
#21
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
In VB6, when the "Debug.Print 1 \ 0" line is executed in the event procedure, I get the following prompt:
Then I can just click "Debug" and skip over the offending line (yellow colored) in the debugger and then execution can resume normally (F5). Clicking "End" also works fine.
Doesn't this debugging feature work in Excel VBA? This is very strange indeed...
Yes it does and I do get this familiar runtime error prompt but after clicking either the Debug or End buttons, I immediately get the the error prompt I showed earlier in post#13
Attachment 192903
And I can't discard that error prompt because it keeps poping up until I kill the excel process via the task manager.
Last edited by AngelV; Sep 18th, 2024 at 03:25 PM.
-
Sep 18th, 2024, 03:23 PM
#22
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by fafalone
VBA UserForms and VB6 forms are very different animals, and VBA does a lot of weird stuff underneath VB6 doesn't or does differently; 64bit is worse.
Remember they're both a major and minor revision apart; they didn't add features beyond PtrSafe/LongPtr and LongLong (the latter in 64bit only), but there were probably substantial internals changes. With 64bit I expect they felt free to ignore compatibility with "undocumented" features like everything related to AddressOf and the *Ptr functions.
So far, I am only compiling a x32bit build of the ActiveX and testing it in Excel x32bit in oder to keep things easy and far from the x64 own issues but still, I am getting all these nasty hiccups already.
-
Sep 18th, 2024, 03:52 PM
#23
Re: RawInput
Originally Posted by VanGoghGaming
Be that as it may, I don't see a reason why VBA shouldn't be able to debug an event procedure (while preventing more events from coming in debug mode) the same as VB6. Unless TwinBasic implemented the WithEvents/RaiseEvent pair in a radically different manner.
I'll try seeing if a VB6 compiled ocx behaves any different tonight.
@AngelV, post the test code you're using?
-
Sep 18th, 2024, 04:47 PM
#24
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by fafalone
@AngelV, post the test code you're using?
This is the minimal test code in the form module to illustrate the problem:
Code:
Option Explicit
Private WithEvents Subclass As prjSafeSubclassing.cSC
Private Declare Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hwnd As Long) As Long
Private Sub Subclass_MessageReceived(hwnd As Long, uMsg As Long, wParam As Long, lParam As Long, dwRefData As Long, bDiscardMessage As Boolean, lReturnValue As Long)
Const WM_MOVE = &H3, WM_SETCURSOR = &H20
'On Error Resume Next
Select Case uMsg
Case WM_SETCURSOR
Debug.Print Now
Case WM_MOVE
Debug.Print 1 \ 0 ' Run-time error 11: Division by zero. We can safely debug and skip past this error in IDE or click "End"
End Select
End Sub
Private Sub UserForm_Activate()
Static bSubclassed As Boolean
Dim hwnd As Long
If bSubclassed Then Exit Sub
Call IUnknown_GetWindow(Me, VarPtr(hwnd))
Set Subclass = New prjSafeSubclassing.cSC
Subclass.SubclassWnd hwnd
bSubclassed = True
End Sub
Private Sub UserForm_Terminate()
Set Subclass = Nothing
End Sub
Last edited by AngelV; Sep 18th, 2024 at 05:47 PM.
-
Sep 18th, 2024, 05:11 PM
#25
Thread Starter
Hyperactive Member
Re: RawInput
And here is a video recording of what is happening : (After the last error prompt, excel shuts down)
-
Sep 18th, 2024, 06:51 PM
#26
Re: RawInput
Just an aside I strongly advise against Win32APi_PtrSafe... I found the error rate way too high to bother.
WinDevLib has 5x the coverage anyway.
-
Sep 18th, 2024, 07:06 PM
#27
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by fafalone
Just an aside I strongly advise against Win32APi_PtrSafe... I found the error rate way too high to bother.
I am not using x64 yet.
WinDevLib has 5x the coverage anyway.
What is WinDevLib ?
-
Sep 18th, 2024, 07:27 PM
#28
Re: RawInput
Okay just for fun I've dug up an old ISO image of Microsoft Office 2003 I had lying around and installed it in a Windows 10 VMWare Virtual Machine. At first VBA didn't even run properly in Excel, it was throwing a dubious error about object being disconnected immediately after displaying the UserForm. After receiving a TON of office updates through Windows Update everything started to work correctly though.
So I created a new VBA Macro, slapped a UserForm on it and set a Reference to the prjSafeSubclassing ActiveX DLL (after registering it with RegSvr32 in an administrator CMD.EXE window). I didn't even know UserForms don't have a "hWnd" property but picked up the "IUnknown_GetWindow" trick from you! Here's the form code:
Code:
Option Explicit
Private WithEvents Subclass As prjSafeSubclassing.cSC
Private Type POINTAPI
X As Long
Y As Long
End Type
Private Type MINMAXINFO
ptReserved As POINTAPI
ptMaxSize As POINTAPI
ptMaxPosition As POINTAPI
ptMinTrackSize As POINTAPI
ptMaxTrackSize As POINTAPI
End Type
Private Type MINMAXSIZE
MinWidth As Long
MaxWidth As Long
MinHeight As Long
MaxHeight As Long
End Type
Private Const WM_GETMINMAXINFO As Long = &H24, WM_CONTEXTMENU As Long = &H7B, WM_HOTKEY As Long = &H312, WS_SIZEBOX As Long = &H40000, _
GWL_STYLE As Long = -16&, MOD_ALT As Long = &H1, MOD_CONTROL As Long = &H2
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Declare Function GetWindowLongW Lib "user32" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
Private Declare Function SetWindowLongW Lib "user32" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong 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 IUnknown_GetWindow Lib "shlwapi" (ByVal pIUnk As IUnknown, hWnd As Long) As Long
Private tMinMaxInfo As MINMAXINFO, tMinMaxSize As MINMAXSIZE, hWnd As Long
Private Sub Subclass_MessageReceived(ByVal hWnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long, ByVal dwRefData As Long, bDiscardMessage As Boolean, lReturnValue As Long)
Select Case uMsg
Case WM_CONTEXTMENU
Debug.Print 1 \ 0 ' Run-time error 11: Division by zero. We can safely debug and skip past this error in IDE or click "End"
Case WM_HOTKEY
If (lParam And &HFFFF&) = (MOD_ALT Or MOD_CONTROL) Then
Select Case lParam \ 65536
Case vbKeyBack ' Press Ctrl-Alt-Backspace to quit (the form doesn't need to be in the foreground)!
Unload Me
End Select
End If
Case WM_GETMINMAXINFO
CheckMinMaxInfo tMinMaxInfo, lParam: bDiscardMessage = True ' We can resize the form only within its confines defined in Form_Load
End Select
End Sub
Private Sub UserForm_Activate()
Static bActivate As Boolean
If Not bActivate Then
bActivate = True: IUnknown_GetWindow Me, hWnd
SetWindowLongW hWnd, GWL_STYLE, GetWindowLongW(hWnd, GWL_STYLE) Or WS_SIZEBOX
RegisterHotKey hWnd, &HABCD&, MOD_ALT Or MOD_CONTROL, vbKeyBack
Subclass.SubclassWnd hWnd
End If
End Sub
Private Sub UserForm_Initialize()
Set Subclass = New prjSafeSubclassing.cSC
With tMinMaxSize
.MinWidth = 200: .MinHeight = 150: .MaxWidth = .MinWidth * 3: .MaxHeight = .MinHeight * 3
End With
End Sub
Private Sub UserForm_Terminate()
UnregisterHotKey hWnd, &HABCD&
End Sub
Private Sub CheckMinMaxInfo(tMinMaxInfo As MINMAXINFO, ByVal lParam As Long)
CopyMemory ByVal VarPtr(lParam) - 4, lParam, 4
With tMinMaxInfo
.ptMinTrackSize.X = tMinMaxSize.MinWidth: .ptMinTrackSize.Y = tMinMaxSize.MinHeight
.ptMaxTrackSize.X = tMinMaxSize.MaxWidth: .ptMaxTrackSize.Y = tMinMaxSize.MaxHeight
End With
End Sub
It subclasses the WM_CONTEXTMENU, WM_HOTKEY and WM_GETMINMAXINFO messages (had to make the UserForm resizable first since apparently it doesn't start that way in VBA).
- WM_CONTEXTMENU: Executes "Debug.Print 1 \ 0" on right-click to throw a runtime error. Clicking Debug, Stop, End all work perfectly fine, no crashes.
- WM_HOTKEY: Press Ctrl-Alt-Backspace to unload the UserForm.
- WM_GETMINMAXINFO: Limits resizing the UserForm between (200:150)-(600:450) pixels.
Now if this code doesn't perform as expected for you then I'd say there's definitely a problem with how TwinBasic compiles ActiveX DLLs since mine was compiled with VB6...
-
Sep 18th, 2024, 07:29 PM
#29
Re: RawInput
Doesnt happen with VB6... Ill add it to the tB bug tracker
-
Sep 18th, 2024, 07:44 PM
#30
Re: RawInput
Originally Posted by AngelV
What is WinDevLib ?
It's basically "oleexp" on steroids but only for TwinBasic.
Originally Posted by fafalone
Doesnt happen with VB6... Ill add it to the tB bug tracker
So I helped discover yet another TB bug? I shouldn't give up my day gig!
-
Sep 18th, 2024, 08:26 PM
#31
Re: RawInput
Originally Posted by AngelV
I am not using x64 yet.
What is WinDevLib ?
Don't bother with x64 right now. It crashes Excel outright; doesn't work at all. I've reported that too now. It works in the tB IDE so it's definitely VBA shenanigans vs bad code. It's weird because 64bit VBCCR and ucShellBrowse work in VBA64, and they have *tons* of subclassing and callbacks.
WinDevLib is oleexp interfaces + 6000+ 64bit-compatible APIs defs redone from scratch, with the added help of grouping constants for arguments into enums for Intellisense. In some places there's tB-only syntax but the APIs are largely copy pastable for VBA; just need to remove attributes like [Description] and [TypeHint] if used, and inline comments; if a UDT is preceded by [PackingAlignment()], those are the only things you can't use in VBA as-is, as well as anything in wdAPIInterlocked. It's in the tB Package Manager or https://github.com/fafalone/WinDevLib
Bug reports for tB are at https://github.com/twinbasic/twinbasic/issues/1908
Last edited by fafalone; Sep 18th, 2024 at 08:31 PM.
-
Sep 18th, 2024, 09:42 PM
#32
Re: RawInput
The fact that the TB ActiveX DLL doesn't fire its Class_Terminate automatically might indicate some sort of lingering reference somewhere internally...
-
Sep 18th, 2024, 10:45 PM
#33
Thread Starter
Hyperactive Member
Re: RawInput
@VanGoghGaming
Here is the feedback on your code in post#28
1- The ActiveX Class instance must be explicitly set to Nothing in the form Terminate event otherwise excel shuts down without warning. This the same as what I experienced my my earlier code.
2- Debug.Print 1\0 brings up the usual runtime error 11 prompt but , just as I explained eralier, after I press the error prompt End or Debug buttons, the nasty 40040 runtime error prompt pops up and the entire excel application crashes afterwards.
So to sum up, your vba code carries the same problems I experienced with my vba code.
-
Sep 18th, 2024, 11:05 PM
#34
Re: RawInput
Yep, you need to compile the ActiveX DLL with VB6 in order to fix both those issues.
-
Sep 18th, 2024, 11:06 PM
#35
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by fafalone
WinDevLib is oleexp interfaces + 6000+ 64bit-compatible APIs defs redone from scratch, ...
Great stuff but quite intimidating Thanks.
I have reported the bug with regards to having to set the ActiveX Class instance to Nothing before closing the form. If the instance is not explicitly released from memory before closing the form, excel shuts down.
-
Sep 18th, 2024, 11:10 PM
#36
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
Yep, you need to compile the ActiveX DLL with VB6 in order to fix both those issues.
Such a shame not only because I don't have VB6 but more so because VB6 can't compile x64 builds which I need in office\excel x64 ... I was raising my hopes with twinbasic but ....
-
Sep 18th, 2024, 11:19 PM
#37
Re: RawInput
Well, until the TwinBasic bug is fixed you could grab my copy of the SafeSubclassing ActiveX DLL if you want. Here it is on a temporary file sharing site: https://temp.sh/MfjuA/SafeSubclassing.zip (they say the link is good for 3 days after which it expires).
-
Sep 18th, 2024, 11:37 PM
#38
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by VanGoghGaming
Well, until the TwinBasic bug is fixed you could grab my copy of the SafeSubclassing ActiveX DLL if you want. Here it is on a temporary file sharing site: https://temp.sh/MfjuA/SafeSubclassing.zip (they say the link is good for 3 days after which it expires).
Your activeX compiled in VB6 works beautifully - Just tested it. None of the above issues ... Thanks. (BTW, I didn't register it ?!!)
-
Sep 18th, 2024, 11:52 PM
#39
Thread Starter
Hyperactive Member
Re: RawInput
Originally Posted by AngelV
Your activeX compiled in VB6 works beautifully - Just tested it. None of the above issues ... Thanks. (BTW, I didn't register it ?!!)
@VanGoghGaming
EDIT:
Works ok with run time errors but not with compile errors when Option Explicit is present... compile errors do crash the whole application. This happens with your vb6 compiled dll ... I though this was worth mentioning.
-
Sep 18th, 2024, 11:53 PM
#40
Re: RawInput
Cool beans, glad it also works for you!
Regarding the registration conundrum, you already had the TB one registered and they have the same ProgId (prjSafeSubclassing.cSC) so if you've overwritten it then it must've picked up the VB6 one instead. Or if you picked it through the "Browse" option in the "References" dialog like I see in your video above then I'm sure that also registers it in place.
Not sure what you mean by "Compile Errors", nothing should be running at compile time so there is nothing to crash? Can you give an example?
Posting Permissions
- You may not post new threads
- You may not post replies
- You may not post attachments
- You may not edit your posts
-
Forum Rules
|
Click Here to Expand Forum to Full Width
|