Skip to content

Commit 5213f16

Browse files
committed
(wip) Revert "X.U.Grab: Hide mkGrabs from XMonad"
Now that we require xmonad 0.18.0, this is no longer needed. This reverts commit 0934fe5.
1 parent 02f124c commit 5213f16

File tree

2 files changed

+6
-50
lines changed

2 files changed

+6
-50
lines changed

Diff for: XMonad/Util/Grab.hs

+4-48
Original file line numberDiff line numberDiff line change
@@ -29,15 +29,12 @@ module XMonad.Util.Grab
2929
) where
3030

3131
-- core
32-
import XMonad hiding (mkGrabs)
32+
import XMonad
3333

3434
import Control.Monad ( when )
35-
import Data.Bits ( setBit )
3635
import Data.Foldable ( traverse_ )
3736
-- base
38-
import qualified Data.Map.Strict as M
3937
import Data.Semigroup ( All(..) )
40-
import Data.Traversable ( for )
4138

4239
-- }}}
4340

@@ -70,9 +67,8 @@ grabUngrab
7067
-> [(KeyMask, KeySym)] -- ^ Keys to ungrab
7168
-> X ()
7269
grabUngrab gr ugr = do
73-
f <- mkGrabs
74-
traverse_ (uncurry ungrabKP) (f ugr)
75-
traverse_ (uncurry grabKP) (f gr)
70+
traverse_ (uncurry ungrabKP) =<< mkGrabs ugr
71+
traverse_ (uncurry grabKP) =<< mkGrabs gr
7672

7773
-- | A convenience function to grab keys. This also ungrabs all
7874
-- previously grabbed keys.
@@ -88,49 +84,9 @@ customRegrabEvHook regr = \case
8884
e@MappingNotifyEvent{} -> do
8985
io (refreshKeyboardMapping e)
9086
when (ev_request e `elem` [mappingKeyboard, mappingModifier])
91-
$ setNumlockMask
87+
$ cacheNumlockMask
9288
>> regr
9389
pure (All False)
9490
_ -> pure (All True)
9591

9692
-- }}}
97-
98-
-- --< Private Utils >-- {{{
99-
100-
-- | Private action shamelessly copied and restyled from XMonad.Main source.
101-
setNumlockMask :: X ()
102-
setNumlockMask = withDisplay $ \dpy -> do
103-
ms <- io (getModifierMapping dpy)
104-
xs <- sequence
105-
[ do
106-
ks <- io (keycodeToKeysym dpy kc 0)
107-
pure $ if ks == xK_Num_Lock
108-
then setBit 0 (fromIntegral m)
109-
else 0 :: KeyMask
110-
| (m, kcs) <- ms
111-
, kc <- kcs
112-
, kc /= 0
113-
]
114-
modify $ \s -> s { numberlockMask = foldr (.|.) 0 xs }
115-
116-
-- | Private function shamelessly copied and refactored from XMonad.Main source.
117-
mkGrabs :: X ([(KeyMask, KeySym)] -> [(KeyMask, KeyCode)])
118-
mkGrabs = withDisplay $ \dpy -> do
119-
let (minCode, maxCode) = displayKeycodes dpy
120-
allCodes = [fromIntegral minCode .. fromIntegral maxCode]
121-
syms <- io . for allCodes $ \code -> keycodeToKeysym dpy code 0
122-
let keysymMap = M.fromListWith (++) (zip syms $ pure <$> allCodes)
123-
keysymToKeycodes sym = M.findWithDefault [] sym keysymMap
124-
extraMods <- extraModifiers
125-
pure $ \ks -> do
126-
(mask, sym) <- ks
127-
keycode <- keysymToKeycodes sym
128-
extraMod <- extraMods
129-
pure (mask .|. extraMod, keycode)
130-
131-
-- }}}
132-
133-
134-
-- NOTE: there is some duplication between this module and core. The
135-
-- latter probably will never change, but this needs to be kept in sync
136-
-- with any potential bugs that might arise.

Diff for: xmonad-contrib.cabal

+2-2
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ library
7676
ghc-options: -Wall -Wno-unused-do-bind
7777

7878
if flag(pedantic)
79-
ghc-options: -Werror -Wwarn=deprecations -Wwarn=dodgy-imports
79+
ghc-options: -Werror -Wwarn=deprecations
8080

8181
-- Keep this in sync with the oldest version in 'tested-with'
8282
if impl(ghc > 8.6.5)
@@ -496,7 +496,7 @@ test-suite tests
496496
default-language: Haskell2010
497497

498498
if flag(pedantic)
499-
ghc-options: -Werror -Wwarn=deprecations -Wwarn=dodgy-imports
499+
ghc-options: -Werror -Wwarn=deprecations
500500

501501
-- Keep this in sync with the oldest version in 'tested-with'
502502
if impl(ghc > 8.6.5)

0 commit comments

Comments
 (0)