X.A.Submap, X.Prompt: Use cleanKeyMask

This replaces the custom `cleanMask` extension in these modules—which
only filtered out XKB group bits and Button5Mask¹—with the new
`cleanKeyMask` which additionally filters out all mouse buttons, as
these aren't relevant for key bindings.

¹) Filtering out Button5Mask was probably an off-by-one mistake.

Fixes: https://github.com/xmonad/xmonad-contrib/issues/290
Related: https://github.com/xmonad/xmonad-contrib/pull/590
This commit is contained in:
Tomas Janousek 2022-02-09 23:53:16 +00:00
parent adced0a8c8
commit 12c5518852
2 changed files with 12 additions and 23 deletions

View File

@ -27,7 +27,7 @@ module XMonad.Actions.Submap (
import Data.Bits import Data.Bits
import qualified Data.Map as M import qualified Data.Map as M
import XMonad hiding (keys) import XMonad hiding (keys)
import XMonad.Prelude (fix, fromMaybe, keyToString) import XMonad.Prelude (fix, fromMaybe, keyToString, cleanKeyMask)
import XMonad.Util.XUtils import XMonad.Util.XUtils
{- $usage {- $usage
@ -138,8 +138,7 @@ waitForKeyPress = do
then nextkey then nextkey
else return (m, keysym) else return (m, keysym)
_ -> return (0, 0) _ -> return (0, 0)
-- Remove num lock mask and Xkb group state bits m' <- cleanKeyMask <*> pure m
m' <- cleanMask $ m .&. ((1 `shiftL` 12) - 1)
io $ do ungrabPointer dpy currentTime io $ do ungrabPointer dpy currentTime
ungrabKeyboard dpy currentTime ungrabKeyboard dpy currentTime
sync dpy False sync dpy False

View File

@ -99,7 +99,6 @@ module XMonad.Prompt
import XMonad hiding (cleanMask, config) import XMonad hiding (cleanMask, config)
import XMonad.Prelude hiding (toList) import XMonad.Prelude hiding (toList)
import qualified XMonad as X (numberlockMask)
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Util.Font import XMonad.Util.Font
import XMonad.Util.Types import XMonad.Util.Types
@ -150,7 +149,7 @@ data XPState =
, offset :: !Int , offset :: !Int
, config :: XPConfig , config :: XPConfig
, successful :: Bool , successful :: Bool
, numlockMask :: KeyMask , cleanMask :: KeyMask -> KeyMask
, done :: Bool , done :: Bool
, modeDone :: Bool , modeDone :: Bool
, color :: XPColor , color :: XPColor
@ -357,9 +356,9 @@ amberXPConfig = def { bgColor = "black"
} }
initState :: Display -> Window -> Window -> Rectangle -> XPOperationMode initState :: Display -> Window -> Window -> Rectangle -> XPOperationMode
-> GC -> XMonadFont -> [String] -> XPConfig -> KeyMask -> Dimension -> GC -> XMonadFont -> [String] -> XPConfig -> (KeyMask -> KeyMask)
-> XPState -> Dimension -> XPState
initState d rw w s opMode gc fonts h c nm width = initState d rw w s opMode gc fonts h c cm width =
XPS { dpy = d XPS { dpy = d
, rootw = rw , rootw = rw
, win = w , win = w
@ -382,7 +381,7 @@ initState d rw w s opMode gc fonts h c nm width =
, successful = False , successful = False
, done = False , done = False
, modeDone = False , modeDone = False
, numlockMask = nm , cleanMask = cm
, prompter = defaultPrompter c , prompter = defaultPrompter c
, color = defaultColor c , color = defaultColor c
, eventBuffer = [] , eventBuffer = []
@ -555,7 +554,7 @@ mkXPromptImplementation :: String -> XPConfig -> XPOperationMode -> X XPState
mkXPromptImplementation historyKey conf om = do mkXPromptImplementation historyKey conf om = do
XConf { display = d, theRoot = rw } <- ask XConf { display = d, theRoot = rw } <- ask
s <- gets $ screenRect . W.screenDetail . W.current . windowset s <- gets $ screenRect . W.screenDetail . W.current . windowset
numlock <- gets X.numberlockMask cleanMask <- cleanKeyMask
cachedir <- asks (cacheDir . directories) cachedir <- asks (cacheDir . directories)
hist <- io $ readHistory cachedir hist <- io $ readHistory cachedir
fs <- initXMF (font conf) fs <- initXMF (font conf)
@ -572,7 +571,7 @@ mkXPromptImplementation historyKey conf om = do
selectInput d w $ exposureMask .|. keyPressMask selectInput d w $ exposureMask .|. keyPressMask
setGraphicsExposures d gc False setGraphicsExposures d gc False
let hs = fromMaybe [] $ M.lookup historyKey hist let hs = fromMaybe [] $ M.lookup historyKey hist
st = initState d rw w s om gc fs hs conf numlock width st = initState d rw w s om gc fs hs conf cleanMask width
runXP st)) runXP st))
releaseXMF fs releaseXMF fs
when (successful st') $ do when (successful st') $ do
@ -595,15 +594,6 @@ mkXPromptImplementation historyKey conf om = do
CenteredAt{ xpWidth } -> floor $ fi (rect_width scr) * xpWidth CenteredAt{ xpWidth } -> floor $ fi (rect_width scr) * xpWidth
_ -> rect_width scr _ -> rect_width scr
-- | Removes numlock and capslock from a keymask.
-- Duplicate of cleanMask from core, but in the
-- XP monad instead of X.
cleanMask :: KeyMask -> XP KeyMask
cleanMask msk = do
numlock <- gets numlockMask
let highMasks = 1 `shiftL` 12 - 1
return (complement (numlock .|. lockMask) .&. msk .&. highMasks)
-- | Inverse of 'Codec.Binary.UTF8.String.utf8Encode', that is, a convenience -- | Inverse of 'Codec.Binary.UTF8.String.utf8Encode', that is, a convenience
-- function that checks to see if the input string is UTF8 encoded before -- function that checks to see if the input string is UTF8 encoded before
-- decoding. -- decoding.
@ -699,7 +689,7 @@ merely discarded, but passed to the respective application window.
handleMain :: KeyStroke -> Event -> XP () handleMain :: KeyStroke -> Event -> XP ()
handleMain stroke@(keysym,_) KeyEvent{ev_event_type = t, ev_state = m} = do handleMain stroke@(keysym,_) KeyEvent{ev_event_type = t, ev_state = m} = do
(compKey,modeKey) <- gets $ (completionKey &&& changeModeKey) . config (compKey,modeKey) <- gets $ (completionKey &&& changeModeKey) . config
keymask <- cleanMask m keymask <- gets cleanMask <*> pure m
-- haven't subscribed to keyRelease, so just in case -- haven't subscribed to keyRelease, so just in case
when (t == keyPress) $ when (t == keyPress) $
if (keymask,keysym) == compKey if (keymask,keysym) == compKey
@ -831,7 +821,7 @@ handleSubmap :: XP ()
-> Event -> Event
-> XP () -> XP ()
handleSubmap defaultAction keymap stroke KeyEvent{ev_event_type = t, ev_state = m} = do handleSubmap defaultAction keymap stroke KeyEvent{ev_event_type = t, ev_state = m} = do
keymask <- cleanMask m keymask <- gets cleanMask <*> pure m
when (t == keyPress) $ handleInputSubmap defaultAction keymap keymask stroke when (t == keyPress) $ handleInputSubmap defaultAction keymap keymask stroke
handleSubmap _ _ stroke event = handleOther stroke event handleSubmap _ _ stroke event = handleOther stroke event
@ -888,7 +878,7 @@ handleBuffer :: (String -> String -> (Bool,Bool))
-> Event -> Event
-> XP () -> XP ()
handleBuffer f stroke event@KeyEvent{ev_event_type = t, ev_state = m} = do handleBuffer f stroke event@KeyEvent{ev_event_type = t, ev_state = m} = do
keymask <- cleanMask m keymask <- gets cleanMask <*> pure m
when (t == keyPress) $ handleInputBuffer f keymask stroke event when (t == keyPress) $ handleInputBuffer f keymask stroke event
handleBuffer _ stroke event = handleOther stroke event handleBuffer _ stroke event = handleOther stroke event