- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In my Quickwin programs I need to trap a variety of extended key codes--arrow, page up, etc. I know that I can use GETCHARQQ and INCHARQQ to get the scan numbers associated with many of these keys, and that the function PASSDIRKEYSQQ is needed to allow some codes to pass. But there are still many codes I cannot trap. For example, alt-anything does not produce anything. The most surprising, and critical, is that shft-tab produces the same code as tab.
There is probably an API function I can call that has more flexibility than the Quickwin functions. Can anybody help me with this?
Link Copied
6 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Trapping keystrokes implies that your program not only is informed of keyboard activity, but also can intercept keystrokes before they are acted on by Windows and prevent Windows from its usual key-driven actions. You can approach this in two ways: first by processing WM_KEYDOWN messages in your program's proc function (probably not available to you in Quickwin), or at a more fundamental level by setting up a hook function.
The following code sample illustrates hook function setup for a program which subclasses the desktop and needs to disable user actions which would affect the program while it is running:
[fortran]
SUBROUTINE LowLevelHooks (mode)
IMPLICIT NONE
INTEGER, INTENT(IN) :: mode
INTEGER :: rval
! (arbitrary) placeholder values for system hotkey structures
INTEGER, PARAMETER :: hk_alttab = 100
INTEGER, PARAMETER :: hk_altesc = 101
! hooking only supported for 32-bit Windows
IF (windows_version == VER_PLATFORM_WIN32_NT) THEN
SELECT CASE (mode)
CASE (1)
! set hooks to trap Windows keys and Enterkey
hHook_keyboard = SetWindowsHookEx (WH_KEYBOARD_LL, &
LOC(KbdHookProc), &
ghInstance, &
NULL)
! cause Windows to send a WM_HOTKEY to the main window
! proc so system (ie, non-hookable) hotkeys can be trapped
rval = RegisterHotKey (ghwndMain, hk_alttab, MOD_ALT, VK_TAB)
rval = RegisterHotKey (ghwndMain, hk_altesc, MOD_ALT, VK_ESCAPE)
CASE (-1)
rval = UnHookWindowsHookEx (hHook_keyboard)
hHook_keyboard = 0
! restore standard system hotkeys
rval = UnregisterHotKey (ghwndMain, hk_alttab)
rval = UnregisterHotKey (ghwndMain, hk_altesc)
END SELECT
END IF
END SUBROUTINE LowLevelHooks
INTEGER FUNCTION KbdHookProc (code, wParam, lParam)
!DEC$ IF DEFINED(_X86_)
!DEC$ ATTRIBUTES STDCALL, ALIAS : '_KbdHookProc@12' :: KbdHookProc
!DEC$ ELSE
!DEC$ ATTRIBUTES STDCALL, ALIAS : 'KbdHookProc' :: KbdHookProc
!DEC$ ENDIF
IMPLICIT NONE
INTEGER, INTENT(IN) :: code
INTEGER(fWPARAM) :: wParam
INTEGER(fLPARAM) :: lParam
INTEGER(HANDLE) :: hfocus
INTEGER :: j
TYPE T_KBDLLHOOKSTRUCTX ! reworked from ifwinty, which is scrambled
SEQUENCE
integer(DWORD) vkCode ! knowns DWORD
integer(DWORD) scanCode ! knowns DWORD
integer(DWORD) flags ! knowns DWORD
integer(DWORD) time ! knowns DWORD
integer(ULONG) dwExtraInfo ! typedefs ULONG_PTR
END TYPE
TYPE(T_KBDLLHOOKSTRUCTX) :: kbs
POINTER(lParam, kbs)
IF (code == HC_ACTION) THEN
SELECT CASE (kbs%vkCode)
CASE (VK_LWIN, VK_RWIN, VK_F4, VK_PRIOR, VK_NEXT)
KbdHookProc = block_further_processing ! value of 1
RETURN
! system hotkeys ctrl+escape and ctrl+shift+escape
CASE (VK_ESCAPE)
IF (IAND(GetAsyncKeyState(VK_CONTROL), Z'8000') /= 0) THEN
KbdHookProc = block_further_processing
RETURN
ELSE IF ((IAND(GetAsyncKeyState(VK_CONTROL), Z'8000') /= 0) .AND. &
(IAND(GetAsyncKeyState(VK_SHIFT ), Z'8000') /= 0) ) THEN
KbdHookProc = block_further_processing
RETURN
END IF
! try for ctrl+alt+del (not expected to work)
!CASE (VK_DELETE)
! IF ((IAND(GetAsyncKeyState(VK_CONTROL), Z'8000') /= 0) .AND. &
! (IAND(kbs%flags, LLKHF_ALTDOWN) /= 0) ) THEN
! KbdHookProc = block_further_processing
! RETURN
! END IF
CASE (VK_UP, VK_DOWN)
IF (hHook_mouse /= 0) THEN
KbdHookProc = block_further_processing
RETURN
END IF
! allow enter when we are shelled out, or for multiline
! and some numeric edit controls only; block all others
CASE (VK_RETURN)
IF (IsWindow(hwnd_ChildProcess) == 0) THEN
IF (n_enterwindows > 0) THEN
hfocus = GetFocus()
DO j = 1, n_enterwindows
IF (hfocus == hwnd_allowenter(j)) GOTO 10
END DO
END IF
KbdHookProc = block_further_processing
RETURN
END IF
END SELECT
! kill the power, sleep and wake keys by blocking their scan codes
! key set1 make set1 break
! power EO5E EODE
! sleep EO5F EODF
! wake EO63 E0E3
SELECT CASE (kbs%scanCode)
CASE (#5E, #DE, #5F, #DF, #63, #E3)
KbdHookProc = block_further_processing
RETURN
END SELECT
END IF
10 KbdHookProc = CallNextHookEx (hHook_keyboard, code, wParam, lParam)
END FUNCTION KbdHookProc
[/fortran]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the very quick response Paul. But wow! A hundred lines of code just to prepare for some code that will eventually trap the keys? Not being a windows programmer this is a big bite for me to swallow. Would it also require this kind of effort if I were working in C++, VB, or (heaven forbid) Java?
It is hard to believe that Quickwin will, with only 2 - 3 lines of code, trap almost every keypress that I need. I can get ctrl-letters, arrowkeys, and the (insert-home-pageup-delete-end-pagedown) group, among others. The only serious one missing is shift-tab. How can it be so difficult for a program to trap and process the tab key but not shift-tab?
I'm afraid I will have to massage my needs to match my capabilities.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It would be pretty much the same in C++, WIth QuickWin, it handles a lot of the Windows interactions for you, so extending it can be a bit of a pain. If you had written directly to the Windows API adding key values wouldn't be very difficult. I don't know about Java.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
What does "written directly to the Windows API" mean? I'm trying to read a key scan code (using INCHARQQ), or possibly read it from the keyboard buffer (using GETCHARQQ). Is there some way to "read directly from the Windows API"?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Not if you're using QuickWin, which is handling all of the keyboard messages. Given that, you have to "hook" into its processing as Paul suggested,
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks Steve. I think I understand now (except for the part about the effort in C++ being similar to that in Fortran Quickwin; I thought "everything" could be done more directly in C++).
Maybe this issue could go into Intel's Quickwin wishlist? It's crazy that I can read a tab keypress but not a shift-tab. Since Quickwin has the capability of passing other keys (arrows, ins, del, others). Seems this could be easily enhanced to pass a bigger variety of keys.

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page