mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
move extraModifiers/cleanMask to Operations.hs
so XMonadContrib can use them
This commit is contained in:
parent
d7d8c586cb
commit
5da458c755
@ -1,4 +1,6 @@
|
||||
module Config where
|
||||
import Graphics.X11.Xlib.Types (Dimension)
|
||||
import Graphics.X11.Xlib (KeyMask)
|
||||
borderWidth :: Dimension
|
||||
logging :: Bool
|
||||
numlockMask :: KeyMask
|
||||
|
6
Main.hs
6
Main.hs
@ -130,12 +130,6 @@ grabButtons dpy rootw = do
|
||||
where grab button mask = grabButton dpy button mask rootw False buttonPressMask
|
||||
grabModeAsync grabModeSync none none
|
||||
|
||||
extraModifiers :: [KeyMask]
|
||||
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
|
||||
|
||||
cleanMask :: KeyMask -> KeyMask
|
||||
cleanMask = (complement (numlockMask .|. lockMask) .&.)
|
||||
|
||||
-- ---------------------------------------------------------------------
|
||||
-- | Event handler. Map X events onto calls into Operations.hs, which
|
||||
-- modify our internal model of the window manager state.
|
||||
|
@ -16,11 +16,11 @@ module Operations where
|
||||
|
||||
import XMonad
|
||||
import qualified StackSet as W
|
||||
import {-# SOURCE #-} Config (borderWidth,logging)
|
||||
import {-# SOURCE #-} Config (borderWidth,logging,numlockMask)
|
||||
|
||||
import Data.Maybe
|
||||
import Data.List (genericIndex, intersectBy, partition, delete)
|
||||
import Data.Bits ((.|.))
|
||||
import Data.Bits ((.|.), (.&.), complement)
|
||||
import Data.Ratio
|
||||
import qualified Data.Map as M
|
||||
|
||||
@ -433,6 +433,15 @@ withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
|
||||
isClient :: Window -> X Bool
|
||||
isClient w = withWindowSet $ return . W.member w
|
||||
|
||||
-- | Combinations of extra modifier masks we need to grab keys/buttons for.
|
||||
-- (numlock and capslock)
|
||||
extraModifiers :: [KeyMask]
|
||||
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
|
||||
|
||||
-- | Strip numlock/capslock from a mask
|
||||
cleanMask :: KeyMask -> KeyMask
|
||||
cleanMask = (complement (numlockMask .|. lockMask) .&.)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- | Floating layer support
|
||||
|
||||
|
Loading…
x
Reference in New Issue
Block a user