Skip to content

Commit

Permalink
X.A.Submap, X.Prompt: Use cleanKeyMask
Browse files Browse the repository at this point in the history
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: #290
Related: #590
  • Loading branch information
liskin committed Feb 10, 2022
1 parent adced0a commit 12c5518
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 23 deletions.
5 changes: 2 additions & 3 deletions XMonad/Actions/Submap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module XMonad.Actions.Submap (
import Data.Bits
import qualified Data.Map as M
import XMonad hiding (keys)
import XMonad.Prelude (fix, fromMaybe, keyToString)
import XMonad.Prelude (fix, fromMaybe, keyToString, cleanKeyMask)
import XMonad.Util.XUtils

{- $usage
Expand Down Expand Up @@ -138,8 +138,7 @@ waitForKeyPress = do
then nextkey
else return (m, keysym)
_ -> return (0, 0)
-- Remove num lock mask and Xkb group state bits
m' <- cleanMask $ m .&. ((1 `shiftL` 12) - 1)
m' <- cleanKeyMask <*> pure m
io $ do ungrabPointer dpy currentTime
ungrabKeyboard dpy currentTime
sync dpy False
Expand Down
30 changes: 10 additions & 20 deletions XMonad/Prompt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,6 @@ module XMonad.Prompt

import XMonad hiding (cleanMask, config)
import XMonad.Prelude hiding (toList)
import qualified XMonad as X (numberlockMask)
import qualified XMonad.StackSet as W
import XMonad.Util.Font
import XMonad.Util.Types
Expand Down Expand Up @@ -150,7 +149,7 @@ data XPState =
, offset :: !Int
, config :: XPConfig
, successful :: Bool
, numlockMask :: KeyMask
, cleanMask :: KeyMask -> KeyMask
, done :: Bool
, modeDone :: Bool
, color :: XPColor
Expand Down Expand Up @@ -357,9 +356,9 @@ amberXPConfig = def { bgColor = "black"
}

initState :: Display -> Window -> Window -> Rectangle -> XPOperationMode
-> GC -> XMonadFont -> [String] -> XPConfig -> KeyMask -> Dimension
-> XPState
initState d rw w s opMode gc fonts h c nm width =
-> GC -> XMonadFont -> [String] -> XPConfig -> (KeyMask -> KeyMask)
-> Dimension -> XPState
initState d rw w s opMode gc fonts h c cm width =
XPS { dpy = d
, rootw = rw
, win = w
Expand All @@ -382,7 +381,7 @@ initState d rw w s opMode gc fonts h c nm width =
, successful = False
, done = False
, modeDone = False
, numlockMask = nm
, cleanMask = cm
, prompter = defaultPrompter c
, color = defaultColor c
, eventBuffer = []
Expand Down Expand Up @@ -555,7 +554,7 @@ mkXPromptImplementation :: String -> XPConfig -> XPOperationMode -> X XPState
mkXPromptImplementation historyKey conf om = do
XConf { display = d, theRoot = rw } <- ask
s <- gets $ screenRect . W.screenDetail . W.current . windowset
numlock <- gets X.numberlockMask
cleanMask <- cleanKeyMask
cachedir <- asks (cacheDir . directories)
hist <- io $ readHistory cachedir
fs <- initXMF (font conf)
Expand All @@ -572,7 +571,7 @@ mkXPromptImplementation historyKey conf om = do
selectInput d w $ exposureMask .|. keyPressMask
setGraphicsExposures d gc False
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))
releaseXMF fs
when (successful st') $ do
Expand All @@ -595,15 +594,6 @@ mkXPromptImplementation historyKey conf om = do
CenteredAt{ xpWidth } -> floor $ fi (rect_width scr) * xpWidth
_ -> 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
-- function that checks to see if the input string is UTF8 encoded before
-- decoding.
Expand Down Expand Up @@ -699,7 +689,7 @@ merely discarded, but passed to the respective application window.
handleMain :: KeyStroke -> Event -> XP ()
handleMain stroke@(keysym,_) KeyEvent{ev_event_type = t, ev_state = m} = do
(compKey,modeKey) <- gets $ (completionKey &&& changeModeKey) . config
keymask <- cleanMask m
keymask <- gets cleanMask <*> pure m
-- haven't subscribed to keyRelease, so just in case
when (t == keyPress) $
if (keymask,keysym) == compKey
Expand Down Expand Up @@ -831,7 +821,7 @@ handleSubmap :: XP ()
-> Event
-> XP ()
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
handleSubmap _ _ stroke event = handleOther stroke event

Expand Down Expand Up @@ -888,7 +878,7 @@ handleBuffer :: (String -> String -> (Bool,Bool))
-> Event
-> XP ()
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
handleBuffer _ stroke event = handleOther stroke event

Expand Down

0 comments on commit 12c5518

Please sign in to comment.