Software Archive
Read-only legacy content
17061 Discussions

Quickwin, Accelerator-Keys

Intel_C_Intel
Employee
554 Views
How can I generate accelerator-keys in a Quickwin-Application
and
how can I generate "fly-out/pop-up"-Sub-Menus in a Quickwin-Application?
It would be no problem to generate the resources for it
but how can I use the accelerator- and menu-resources?

many thanks
Burkhard Meyer
0 Kudos
7 Replies
Jugoslav_Dujic
Valued Contributor II
554 Views
AFAIK classic accelerators are out in QuickWin. The best you could achieve is to subclass QuickWin windows and intercept WM_KEYDOWN.

As for popup menus, here's a code snippet from an actual app which adds popup sub-menus to a QuickWin menu. Note that you have to subclass the window containing the menu in order to catch WM_COMMAND messages from these items.

 
SUBROUTINE AdditionalMenus 
 
USE COMCTL 
USE MSFWIN 
USE MSFLIB 
USE REGISTRY 
 
IMPLICIT INTEGER(h-n) 
 
INCLUDE 'Resource.fd' 
 
CHARACTER*24::      szMenuName(0:3)=(/'&Topology Analyser�    'C,      & 
                                      '&Load Flow�            'C,      & 
                                      'State &Estimation�     'C/) 
CHARACTER*32::      szItemName(4,0:3)=                                  & 
                             (/'&Voltage level coloring�     'C,       & 
                               '&Area coloring�              'C,       & 
                               '&Feeder coloring�            'C,       & 
                               '&Energization coloring�      'C,       & 
                               '&Display options...�         'C,       & 
                               '�                            'C,       & 
                               '�                            'C,       & 
                               '�                            'C,       & 
                               '&Options...�                 'C,       & 
                               '&Show toolbar�               'C,       & 
                               '�                            'C,       & 
                               '�                            'C,       & 
                               '&Voltage quality�            'C,       & 
                               'Operation planning�          'C,       & 
                               '�                            'C,       & 
                               '�                            'C/) 
 
INTEGER,PARAMETER::     nItems(0:3)=(/4,1,2,4/) 
INTEGER,PARAMETER::     IDItem(4,0:3)=                                  & 
                        (/ID_BUTTON_PONAP,                              & 
                          ID_BUTTON_POGRA,                              & 
                          ID_BUTTON_POIZV,                              & 
                          ID_BUTTON_POSTA,                              & 
                          ID_BUTTON_TS,                                 & 
                          0,0,0,                                        & 
                          ID_BUTTON_ESTOPC,                             & 
                          ID_BUTTON_VREME,                              & 
                          0,0,                                          & 
                          ID_BUTTON_OPTIMALNINAPON,                     & 
                          ID_BUTTON_KVALITETNAPONA,                     & 
                          0,                                            & 
                          ID_BUTTON_OPPLAN/) 
 
hMenu=GetMenu(hFrame) 
hMenu1=GetSubMenu(hMenu,0) 
DO i=0,3 
      hAddMenu=CreatePopupMenu() 
      DO j=1,nItems(i) 
            iFlags=MF_BYPOSITION.OR.MF_STRING.OR.MF_ENABLED 
            IF (i.EQ.0 .AND. j.EQ.4) iFlags=IOR(iFlags,MF_CHECKED) 
            IF (i.EQ.3 .AND. j.EQ.3) iFlags=MF_BYPOSITION.OR.MF_SEPARATOR 
            iSt=AppendMenu(hAddMenu,iFlags,IDItem(j,i),LOC(szItemName(j,i))) 
!            iSt=SetM
enuItemBitmaps(hAddMenu,j-1,MF_BYPOSITION,hBojenjeBmp(j),hBojenjeBmp(j)) 
      END DO 
      iSt=ModifyMenu(hMenu1,i,MF_BYPOSITION.OR.MF_POPUP.OR.MF_STRING.OR.MF_ENABLED, & 
                     hAddMenu,LOC(szMenuName(i))) 
END DO 
 
END SUBROUTINE AdditionalMenus 


Note that in the sample menus are created at run-time using CreatePopupMenu. It's probably possible to use LoadMenu from resources, though I didn't try it. Actuall
0 Kudos
Jugoslav_Dujic
Valued Contributor II
554 Views
...continued

Note that in the sample menus are created at run-time using CreatePopupMenu. It's probably possible to use LoadMenu from resources, though I didn't try it. Actually, it adds four popup menus to the first four items of leftmost QuickWin submenu. nItems is number of items in each sub-submenu, szItemName names of items, IDItem are item IDs (added manually into .rc file, though any set of IDs will serve). hFrame is QW frame window (GetHWNDQQ(QWIN$FRAMEWINDOW)). As noted above, you'll need to subclass hFrame (SetWindowLong(GWL_WNDPROC)). If you're not familiar with it, you may refer to DFWIN samples or search for, say, GWL_WNDPROC in the Forum for few samples. You'll have to catch WM_COMMAND and test whether LOWORD(wParam) matches any of IDs assigned to menu.

HTH

Jugoslav
0 Kudos
Intel_C_Intel
Employee
554 Views
Thank you for your help.
I successfully created a popup-menu and "MyWndProc".
I receive the WM_COMMAND-Messages and the ID-No's for
the popup-menu-selection. Wonderful.
But I don't receive any WM_KEYDOWN-message in "MyWndProc"
to get the codes for accelerator-keys.
What could solve this problem?
0 Kudos
Jugoslav_Dujic
Valued Contributor II
554 Views
The problem is that WM_KEYDOWN is sent to the window which has keyboard focus; in a QuickWin app that's usually a MDI child. However, that implies that you should subclass all child windows in order to have that effect.

A better method would be to use a keyboard hook for your application. Hooking is similar to subclassing, except that it works on a "higher level", i.e. it filters messages before they reach any window in the application. The following hook watches for release of "Ctrl" key in windows hFrame and hChild and does something when it's released. You could easily adapt it by testing for different key(s) (see description of "KeyboardProc" in help).

 
!Of course, explicit interface for KeyboardProc here. 
hKbHook=SetWindowsHookEx(WH_KEYBOARD,LOC(KeyboardProc),NULL,0) 
 
!============================================================== 
INTEGER(4) FUNCTION KeyboardProc(nCode,wParam,lParam)  
!DEC$ATTRIBUTES STDCALL::      KeyboardProc 
 
USE DFWIN 
USE COMCTL 
USE GLOBALS 
USE REGISTRY 
 
IMPLICIT NONE 
 
INTEGER,INTENT(IN)::    nCode,wParam,lParam 
INTEGER::               hFocus 
LOGICAL::               bSt 
TYPE(T_POINT)::         PT 
 
INTEGER::               iEvent,  & 
                        nKey,    & 
                        iSt 
 
INCLUDE "Resource.fd" 
 
IF (nCode.LT.0) THEN 
      KeyboardProc=CallNextHookEx(hHook,nCode,wParam,lParam)  
      RETURN 
END IF 
 
!Bit 31 specifies transition state of the key 
nKey=wParam 
IF (IAND(lParam,ISHFT(1,31)) .NE.0) THEN 
      iEvent=WM_KEYUP 
ELSE 
      iEvent=WM_KEYDOWN 
END IF 
 
hFocus=GetFocus() 
IF ((hFocus.EQ.hFrame .OR. hFocus.EQ.hChild) .AND. iEvent.EQ.WM_KEYUP) THEN 
      SELECT CASE (wParam) 
      CASE (VK_CONTROL) 
            IF (PROMENA_ZUMA) THEN 
                  PROMENA_ZUMA=.FALSE. 
                  iSt=ReleaseCapture() 
                  CALL SetDefAppCursor() 
                  CALL Draw(Zum, -1. ,-1.) 
            END IF 
      END SELECT 
END IF 
 
KeyboardProc=CallNextHookEx(hKbHook,nCode,wParam,lParam) 
 
END FUNCTION KeyboardProc 


Note that, like with subclassing, hKbHook variable has to be globally saved and the hook has to CallNextHookEx so that it doesn't break existing hook system.

HTH

Jugoslav
0 Kudos
isn-removed200637
554 Views
Of course you still have the ability to use letter1letter2 where 'letter1' is the
letter preceded by '&' in the text tag of one of the main QUickWin window's menu item's and 'letter2' is the
letter preceded by '&' in a text tag in the drop-down menu that letter1 opens.
0 Kudos
Intel_C_Intel
Employee
554 Views
Thank you for your Help.
But still I couldn't make the solution for the accelerator keys work.
Using "hKbHook= SetWindowsHookEx(WH_KEYBOARD_LL,LOC(MyKbProc),NULL,0)" etc. was not successful. I don't receive any message in MyKbProc. What could be the problem? Many thanks, Burkhard
0 Kudos
Jugoslav_Dujic
Valued Contributor II
554 Views
You should use WH_KEYBOARD, not WH_KEYBOARD_LL. WH_KEYBOARD_LL should be used for system-wide low-level hooks; WH_KEYBOARD is sufficient. Moreover, the routine that calls SetWindowsHookEx should have an knowledge that MyKbProc is local procedure somehow (do you use IMPLICIT NONE?). Maybe EXTERNAL would suffice -- I'm not sure -- I always use either INTERFACE blocks
or MODULE association.

HTH

Jugoslav
0 Kudos
Reply