Skip to content

Commit

Permalink
Add stripModMask to customize cleanMask/extraModifiers
Browse files Browse the repository at this point in the history
  • Loading branch information
liskin committed Feb 10, 2022
1 parent 906b9d3 commit 6a7f648
Show file tree
Hide file tree
Showing 5 changed files with 28 additions and 10 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Expand Up @@ -6,6 +6,10 @@

* Added custom cursor shapes for resizing and moving windows.

* Added `stripModMask` to allow customizing which modifiers are irrelevant
for key bindings. Useful for binding numpad keys only when Num Lock is
off, or to make Mod5 irrelevant in addition to the default Num/Caps Lock.

### Bug Fixes

* Fixed border color of windows with alpha channel. Now all windows have the
Expand Down
12 changes: 11 additions & 1 deletion src/XMonad/Config.hs
Expand Up @@ -38,6 +38,7 @@ import XMonad.Layout
import XMonad.Operations
import XMonad.ManageHook
import qualified XMonad.StackSet as W
import Control.Monad.State (gets)
import Data.Bits ((.|.))
import Data.Default.Class
import Data.Monoid
Expand All @@ -58,14 +59,22 @@ import Graphics.X11.Xlib.Extras
workspaces :: [WorkspaceId]
workspaces = map show [1 .. 9 :: Int]

-- | modMask lets you specify which modkey you want to use. The default
-- | 'modMask' lets you specify which modkey you want to use. The default
-- is mod1Mask ("left alt"). You may also consider using mod3Mask
-- ("right alt"), which does not conflict with emacs keybindings. The
-- "windows key" is usually mod4Mask.
--
defaultModMask :: KeyMask
defaultModMask = mod1Mask

-- | 'stripModMask' lets you specify which modifiers are irrelevant for key
-- bindings. The default is Num Lock and Caps Lock. You will need to override
-- this if you wish to only strip Caps Lock if you need to bind numpad keys
-- but only when Num Lock is off (or on). Another use case is adding
-- 'mod5Mask' to the list of stripped/irrelevant modifiers.
defaultStripModMask :: X KeyMask
defaultStripModMask = gets ((lockMask .|.) . numberlockMask)

-- | Width of the window border in pixels.
--
borderWidth :: Dimension
Expand Down Expand Up @@ -264,6 +273,7 @@ instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) wh
, XMonad.normalBorderColor = normalBorderColor
, XMonad.focusedBorderColor = focusedBorderColor
, XMonad.modMask = defaultModMask
, XMonad.stripModMask = defaultStripModMask
, XMonad.keys = keys
, XMonad.logHook = logHook
, XMonad.startupHook = startupHook
Expand Down
1 change: 1 addition & 0 deletions src/XMonad/Core.hs
Expand Up @@ -111,6 +111,7 @@ data XConfig l = XConfig
-- event hooks in most cases.
, workspaces :: ![String] -- ^ The list of workspaces' names
, modMask :: !KeyMask -- ^ the mod modifier
, stripModMask :: !(X KeyMask) -- ^ The mask of modifiers to ignore in key bindings. Default: num/caps lock.
, keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
-- ^ The key binding: a map from key presses and actions
, mouseBindings :: !(XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
Expand Down
19 changes: 11 additions & 8 deletions src/XMonad/Operations.hs
Expand Up @@ -56,8 +56,8 @@ import qualified XMonad.StackSet as W

import Data.Maybe
import Data.Monoid (Endo(..),Any(..))
import Data.List (nub, (\\), find)
import Data.Bits ((.|.), (.&.), complement, testBit)
import Data.List (nub, (\\), find, foldl', subsequences)
import Data.Bits ((.|.), (.&.), complement, bit, testBit, clearBit, countTrailingZeros)
import Data.Function (on)
import Data.Ratio
import qualified Data.Map as M
Expand Down Expand Up @@ -500,17 +500,20 @@ 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)
-- (by default numlock and capslock, can be overridden in 'stripModMask')
extraModifiers :: X [KeyMask]
extraModifiers = do
nlm <- gets numberlockMask
return [0, nlm, lockMask, nlm .|. lockMask ]
smm <- join $ asks $ stripModMask . config
return $ map (foldl' (.|.) 0) (subsequences (bits smm))
where
bits 0 = []
bits n = let b = countTrailingZeros n in bit b : bits (n `clearBit` b)

-- | Strip numlock\/capslock from a mask.
-- | Strip 'stripModMask' (by default numlock\/capslock) from a mask.
cleanMask :: KeyMask -> X KeyMask
cleanMask km = do
nlm <- gets numberlockMask
return (complement (nlm .|. lockMask) .&. km)
smm <- join $ asks $ stripModMask . config
return (complement smm .&. km)

-- | Set the 'Pixel' alpha value to 255.
setPixelSolid :: Pixel -> Pixel
Expand Down
2 changes: 1 addition & 1 deletion xmonad.cabal
@@ -1,5 +1,5 @@
name: xmonad
version: 0.17.0.9
version: 0.17.0.91
synopsis: A tiling window manager
description: xmonad is a tiling window manager for X. Windows are arranged
automatically to tile the screen without gaps or overlap, maximising
Expand Down

0 comments on commit 6a7f648

Please sign in to comment.