move extraModifiers/cleanMask to Operations.hs

so XMonadContrib can use them
This commit is contained in:
Jason Creighton
2007-06-06 00:50:56 +00:00
parent d7d8c586cb
commit 5da458c755
3 changed files with 13 additions and 8 deletions

View File

@@ -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