xmonad
xmonad copied to clipboard
Key bindings ignore numlock state
Problem Description
I've got a keyboard which uses some keys on the numpad as volume up / volume down / mute keys if numlock is off, and normal numbers and operators if numlock is on. I'm trying to bind them so my volume up / down / mute keys actually work, but xmonad ignores numlock state, so my key bindings always trigger, even if numlock is on, which means I can't use my numpad.
I know xmonad 0.9 used to have a numlockMask config option which could disable this behavior, but it got deprecated and I guess removed since it doesn't work anymore: https://wiki.haskell.org/Xmonad/Config_archive/Template_xmonad.hs_(0.9). I see the current code refers to numberlockMask in some places and numlock is ignored because of cleanMask in this place: https://github.com/xmonad/xmonad/blob/master/src/XMonad/Main.hs#L295, is it even possible to use them to fix this problem? I can't find anyone using those in their config file and I'm too new to Haskell to know if I can somehow override them or write my own function to handle key bindings bypassing XMonad's one. I've been reading the docs on hackage for days, but can't find anything helpful.
Ideally I'd like to disable ignoring numlock key only for those key bindings which happen to use the numpad on my keyboard, but disabling it for all key bindings is a viable solution too since I would still be able to make both work.
I'm using xmonad 0.13 from Arch' repo, I tried to fiddle with the code from master and rebuild it from source (which is still an ugly solution, but better than nothing) but cabal fails to configure it due to "Encountered missing dependencies: semigroups -any" and I don't know how to solve it either, installing semigroups, whatever that is, manually doesn't work, so nope, I didn't check it on code from master nor xmonad-testing.
Configuration File
import XMonad
import System.Exit
import Graphics.X11.ExtraTypes.XF86
import qualified Data.Map as M
main = xmonad def
{ modMask = mod4Mask
, keys = cKeyBindings }
cKeyBindings conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
[ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
, ((modm, xK_p ), spawn "dmenu_run")
, ((modm .|. shiftMask, xK_Escape), io (exitWith ExitSuccess))
, ((modm , xK_Escape), spawn "xmonad --recompile; xmonad --restart")
, ((0 , xF86XK_AudioMute), spawn "xmessage works") ]
Checklist
-
[x] I've read CONTRIBUTING.md
-
[ ] I tested my configuration with xmonad-testing
Half a year later, I switched to an easier distro (Gentoo), so I can finally compile xmonad. I still have no idea if there is a way to do it in a config file but here's a patch for xmonad to make it stop ignoring numlock state, if anyone's interested:
diff --git a/src/XMonad/Operations.hs b/src/XMonad/Operations.hs
index 4b46571..ef3978f 100644
--- a/src/XMonad/Operations.hs
+++ b/src/XMonad/Operations.hs
@@ -423,17 +423,15 @@ 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)
+-- (capslock)
extraModifiers :: X [KeyMask]
extraModifiers = do
- nlm <- gets numberlockMask
- return [0, nlm, lockMask, nlm .|. lockMask ]
+ return [0, lockMask]
--- | Strip numlock\/capslock from a mask
+-- | Strip capslock from a mask
cleanMask :: KeyMask -> X KeyMask
cleanMask km = do
- nlm <- gets numberlockMask
- return (complement (nlm .|. lockMask) .&. km)
+ return (complement lockMask .&. km)
-- | Get the 'Pixel' value for a named color
initColor :: Display -> String -> IO (Maybe Pixel)
I'm not sure if removing stuff from extraModifiers is needed, but it seems consistent to do it and it works. Unfortunatelly I have to duplicate most of my key bindings in my config file now, so it gets messy, but at least it's possible to do.
There's discussion of a related issue in xmonad-contrib - https://github.com/xmonad/xmonad-contrib/issues/290 - since XMonad.Prompt has its own cleanMask
Ignoring numlock state is probably intended. As in you want your key bindings perform the same regardless of numlock state. On many keyboards the key is missing and the state is not displayed anywhere. Same for capslock.
Ignoring numlock state is probably intended. As in you want your key bindings perform the same regardless of numlock state. On many keyboards the key is missing and the state is not displayed anywhere. Same for capslock.
Is there a way to override this? I WANT my keybindings to be different depending on capslock and numlock state and be able to write key-bindings like
, ((modm, xKey), do something)
, ((modm .|. lockMask, xKey), do somethingElse) -- do this when capslock in on
, ((modm .|. mod2Mask, xKey), do somethingDifferent) -- do this when numlock is on
While xmonad processes an event, the event is stored inside XConf. From that, the uncleaned modifier mask can be extracted.
The following code is a possible implementation of the requested behavior.
import XMonad
import Data.Bits ((.&.))
currentModifiers :: X (Maybe KeyMask)
currentModifiers = do
event <- asks currentEvent
pure $ case event of
Just (KeyEvent { ev_state = modifiers }) -> Just modifiers
_ -> Nothing
onModifierState :: KeyMask -> X () -> X () -> X ()
onModifierState wanted ifActive ifInactive = do
modifiers <- currentModifiers
case modifiers of
Just mods
| mods .&. wanted == wanted -> ifActive
| otherwise -> ifInactive
_ -> pure ()
onNumLockState :: X () -> X () -> X ()
onNumLockState ifActive ifInactive = do
numLock <- gets numberlockMask
onModifierState numLock ifActive ifInactive
onCapsLockState :: X () -> X () -> X ()
onCapsLockState = onModifierState lockMask
Using this, a keybinding might look like this:
, ((0, xF86XK_AudioMute), onNumLockState (xmessage "num lock is on") (xmessage "num lock is off"))
Note that this key binding will not trigger if any modifer which is not cleaned by XMonad is active. (The set of cleaned modifiers is num lock and caps lock.)
if someone still needs this, I could create a pull request to add this as a module to xmonad-contrib.
I think there's one problem with @ibbem's solution: xmonad still configures passive grabs for the key with all extraModifiers combinations, which means those numpad keys are grabbed even while numlock is on and their keypresses are delivered to xmonad rather than the current window.
I suspect that we might need to add a stripMask :: X KeyMask (or ignoreMask or something) defaulting to (lockMask .|.) <$> gets numberlockMask to XConfig and rewrite extraModifiers/cleanMask to use it. Then people can override this to not strip numlock mask and not grab keys with numlock mask set (and duplicate keybindings where ignoring numlock is desired).
I suspect that we might need to add a
stripMask :: X KeyMask…
Implemented in https://github.com/xmonad/xmonad/pull/374, and I've also opened https://github.com/xmonad/xmonad-contrib/pull/686 to address Michael's https://github.com/xmonad/xmonad-contrib/issues/290.