mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 21:21:52 -07:00
ignore numlock/capslock on mouse bindings
This commit is contained in:
@@ -3,3 +3,4 @@ import Graphics.X11.Xlib.Types (Dimension)
|
|||||||
import Graphics.X11.Xlib (KeyMask)
|
import Graphics.X11.Xlib (KeyMask)
|
||||||
borderWidth :: Dimension
|
borderWidth :: Dimension
|
||||||
modMask :: KeyMask
|
modMask :: KeyMask
|
||||||
|
numlockMask :: KeyMask
|
||||||
|
3
Main.hs
3
Main.hs
@@ -106,8 +106,7 @@ grabKeys dpy rootw = do
|
|||||||
kc <- keysymToKeycode dpy sym
|
kc <- keysymToKeycode dpy sym
|
||||||
-- "If the specified KeySym is not defined for any KeyCode,
|
-- "If the specified KeySym is not defined for any KeyCode,
|
||||||
-- XKeysymToKeycode() returns zero."
|
-- XKeysymToKeycode() returns zero."
|
||||||
when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) $
|
when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) extraModifiers
|
||||||
[0, numlockMask, lockMask, numlockMask .|. lockMask]
|
|
||||||
|
|
||||||
where grab kc m = grabKey dpy kc m rootw True grabModeAsync grabModeAsync
|
where grab kc m = grabKey dpy kc m rootw True grabModeAsync grabModeAsync
|
||||||
|
|
||||||
|
@@ -15,7 +15,7 @@ module Operations where
|
|||||||
|
|
||||||
import XMonad
|
import XMonad
|
||||||
import qualified StackSet as W
|
import qualified StackSet as W
|
||||||
import {-# SOURCE #-} Config (borderWidth, modMask)
|
import {-# SOURCE #-} Config (borderWidth, modMask, numlockMask)
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.List (genericIndex, intersectBy, partition, delete)
|
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. Tell whether or not to intercept clicks on a given window
|
||||||
setButtonGrab :: Bool -> Window -> X ()
|
setButtonGrab :: Bool -> Window -> X ()
|
||||||
setButtonGrab grab w = withDisplay $ \d -> io $ do
|
setButtonGrab grabAll w = withDisplay $ \d -> io $ do
|
||||||
when (not grab) $ ungrabButton d anyButton anyModifier w
|
when (not grabAll) $ ungrabButton d anyButton anyModifier w
|
||||||
grabButton d anyButton mask w False (buttonPressMask .|. buttonReleaseMask)
|
mapM_ (grab d) masks
|
||||||
grabModeAsync grabModeSync none none
|
where masks = if grabAll then [anyModifier] else map (modMask .|.) extraModifiers
|
||||||
where mask = if grab then anyModifier else modMask
|
grab d m = grabButton d anyButton m w False (buttonPressMask .|. buttonReleaseMask)
|
||||||
|
grabModeAsync grabModeSync none none
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Setting keyboard focus
|
-- Setting keyboard focus
|
||||||
|
Reference in New Issue
Block a user