summaryrefslogtreecommitdiffstats
path: root/XMonad/Stockholm/Submap.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Stockholm/Submap.hs')
-rw-r--r--XMonad/Stockholm/Submap.hs31
1 files changed, 31 insertions, 0 deletions
diff --git a/XMonad/Stockholm/Submap.hs b/XMonad/Stockholm/Submap.hs
new file mode 100644
index 0000000..8648e6c
--- /dev/null
+++ b/XMonad/Stockholm/Submap.hs
@@ -0,0 +1,31 @@
+-- This module is based on Jason Creighton's XMonad.Actions.Submap
+
+module XMonad.Stockholm.Submap
+ ( submapString
+ ) where
+
+import qualified Data.Map as M
+import Control.Monad.Fix (fix)
+import Data.Bits
+import XMonad hiding (keys)
+
+
+-- | Like 'XMonad.Actions.Submap.submapDefault', but provides the looked up string to the default action.
+submapString :: (String -> X ()) -> M.Map (KeyMask, KeySym) (X ()) -> X ()
+submapString def keys = do
+ XConf { theRoot = root, display = d } <- ask
+
+ (m, s, str) <- io $ allocaXEvent $ \p -> fix $ \nextkey -> do
+ maskEvent d keyPressMask p
+ KeyEvent { ev_keycode = code, ev_state = m } <- getEvent p
+ keysym <- keycodeToKeysym d code 0
+ if isModifierKey keysym
+ then nextkey
+ else do
+ (mbKeysym, str) <- lookupString (asKeyEvent p)
+ return (m, keysym, str)
+
+ -- Remove num lock mask and Xkb group state bits
+ m' <- cleanMask $ m .&. ((1 `shiftL` 12) - 1)
+
+ maybe (def str) id (M.lookup (m', s) keys)