ignore numlock/capslock on mouse bindings

This commit is contained in:
Jason Creighton
2007-06-01 01:51:37 +00:00
parent 9669c26fdc
commit b46a449baf
3 changed files with 12 additions and 8 deletions

View File

@@ -3,3 +3,4 @@ import Graphics.X11.Xlib.Types (Dimension)
import Graphics.X11.Xlib (KeyMask)
borderWidth :: Dimension
modMask :: KeyMask
numlockMask :: KeyMask

View File

@@ -106,8 +106,7 @@ grabKeys dpy rootw = do
kc <- keysymToKeycode dpy sym
-- "If the specified KeySym is not defined for any KeyCode,
-- XKeysymToKeycode() returns zero."
when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) $
[0, numlockMask, lockMask, numlockMask .|. lockMask]
when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) extraModifiers
where grab kc m = grabKey dpy kc m rootw True grabModeAsync grabModeAsync

View File

@@ -15,7 +15,7 @@ module Operations where
import XMonad
import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth, modMask)
import {-# SOURCE #-} Config (borderWidth, modMask, numlockMask)
import Data.Maybe
import Data.List (genericIndex, intersectBy, partition, delete)
@@ -239,13 +239,17 @@ rescreen = do
-- ---------------------------------------------------------------------
extraModifiers :: [KeyMask]
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
setButtonGrab :: Bool -> Window -> X ()
setButtonGrab grab w = withDisplay $ \d -> io $ do
when (not grab) $ ungrabButton d anyButton anyModifier w
grabButton d anyButton mask w False (buttonPressMask .|. buttonReleaseMask)
grabModeAsync grabModeSync none none
where mask = if grab then anyModifier else modMask
setButtonGrab grabAll w = withDisplay $ \d -> io $ do
when (not grabAll) $ ungrabButton d anyButton anyModifier w
mapM_ (grab d) masks
where masks = if grabAll then [anyModifier] else map (modMask .|.) extraModifiers
grab d m = grabButton d anyButton m w False (buttonPressMask .|. buttonReleaseMask)
grabModeAsync grabModeSync none none
-- ---------------------------------------------------------------------
-- Setting keyboard focus