aboutsummaryrefslogtreecommitdiffstats
path: root/Operations.hs
diff options
context:
space:
mode:
authorJason Creighton <jcreigh@gmail.com>2007-06-01 03:51:37 +0200
committerJason Creighton <jcreigh@gmail.com>2007-06-01 03:51:37 +0200
commitd7eafb9fb70b60d5f710ab290cb4f4b085c04c99 (patch)
treeb3fdcc5997eab31b4c73299027a5b609666569bc /Operations.hs
parent5a419b7230fefb116b9c914a6ffb2de296b7932b (diff)
downloadxmonad-d7eafb9fb70b60d5f710ab290cb4f4b085c04c99.tar.gz
xmonad-d7eafb9fb70b60d5f710ab290cb4f4b085c04c99.tar.xz
xmonad-d7eafb9fb70b60d5f710ab290cb4f4b085c04c99.zip
ignore numlock/capslock on mouse bindings
darcs-hash:20070601015137-b9aa7-51c6b9ec428c2d16d65b196384fa2ce953dda245.gz
Diffstat (limited to 'Operations.hs')
-rw-r--r--Operations.hs16
1 files changed, 10 insertions, 6 deletions
diff --git a/Operations.hs b/Operations.hs
index f1f5b21..1a25e99 100644
--- a/Operations.hs
+++ b/Operations.hs
@@ -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