aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks
diff options
context:
space:
mode:
authorBrandon S Allbery KF8NH <allbery.b@gmail.com>2011-02-24 03:36:13 +0100
committerBrandon S Allbery KF8NH <allbery.b@gmail.com>2011-02-24 03:36:13 +0100
commit302efadffa33887145a598a0a56903e37c3e65f6 (patch)
treef38217618dfb32f4ef73f6f77645c662b88e1081 /XMonad/Hooks
parente99226d1d73b349ae5962e0f3230e3263c41be08 (diff)
downloadXMonadContrib-302efadffa33887145a598a0a56903e37c3e65f6.tar.gz
XMonadContrib-302efadffa33887145a598a0a56903e37c3e65f6.tar.xz
XMonadContrib-302efadffa33887145a598a0a56903e37c3e65f6.zip
XMonad/Hooks/DebugKeyEvents - debug helper to see what keys xmonad sees
Ignore-this: 5a6a99b7fcc31236152a82aa9c2cda16 darcs-hash:20110224023613-8238f-25d3f73ee0b88c110e58ea8dc008010b4582886d.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r--XMonad/Hooks/DebugKeyEvents.hs107
1 files changed, 107 insertions, 0 deletions
diff --git a/XMonad/Hooks/DebugKeyEvents.hs b/XMonad/Hooks/DebugKeyEvents.hs
new file mode 100644
index 0000000..edacb6c
--- /dev/null
+++ b/XMonad/Hooks/DebugKeyEvents.hs
@@ -0,0 +1,107 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Hooks.DebugKeyEvents
+-- Copyright : (c) 2011 Brandon S Allbery <allbery.b@gmail.com>
+-- License : BSD
+--
+-- Maintainer : Brandon S Allbery <allbery.b@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A debugging module to track key events, useful when you can't tell whether
+-- xmonad is processing some or all key events.
+-----------------------------------------------------------------------------
+
+module XMonad.Hooks.DebugKeyEvents (-- * Usage
+ -- $usage
+ debugKeyEvents
+ ) where
+
+import XMonad.Core
+import XMonad.Operations (cleanMask)
+
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras
+
+import Control.Monad.State (gets)
+import Data.Bits
+import Data.List (intercalate)
+import Data.Monoid
+import Numeric (showHex)
+import System.IO (hPutStrLn
+ ,stderr)
+
+-- $usage
+-- Add this to your handleEventHook to print received key events to the
+-- log (the console if you use @startx@/@xinit@, otherwise usually
+-- @~/.xsession-errors@).
+--
+-- > , handleEventHook = debugKeyEvents
+--
+-- If you already have a handleEventHook then you should append it:
+--
+-- > , handleEventHook = ... <+> debugKeyEvents
+--
+-- Logged key events look like:
+--
+-- @keycode 53 sym 120 (0x78, "x") mask 0x0 () clean 0x0 ()@
+--
+-- The @mask@ and @clean@ indicate the modifiers pressed along with
+-- the key; @mask@ is raw, and @clean@ is what @xmonad@ sees after
+-- sanitizing it (removing @numberLockMask@, etc.)
+--
+-- For more detailed instructions on editing the logHook see:
+--
+-- "XMonad.Doc.Extending#The_log_hook_and_external_status_bars"
+
+-- | Print key events to stderr for debugging
+debugKeyEvents :: Event -> X All
+debugKeyEvents (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
+ | t == keyPress =
+ withDisplay $ \dpy -> do
+ sym <- io $ keycodeToKeysym dpy code 0
+ msk <- cleanMask m
+ nl <- gets numberlockMask
+ io $ hPutStrLn stderr $ intercalate " " ["keycode"
+ ,show code
+ ,"sym"
+ ,show sym
+ ," ("
+ ,hex sym
+ ," \""
+ ,keysymToString sym
+ ,"\") mask"
+ ,hex m
+ ,"(" ++ vmask nl m ++ ")"
+ ,"clean"
+ ,hex msk
+ ,"(" ++ vmask nl msk ++ ")"
+ ]
+ return (All True)
+debugKeyEvents _ = return (All True)
+
+-- | Convenient showHex variant
+hex :: Integral n => n -> String
+hex v = "0x" ++ showHex v ""
+
+-- | Convert a modifier mask into a useful string
+vmask :: KeyMask -> KeyMask -> String
+vmask numLockMask msk = intercalate " " $
+ reverse $
+ fst $
+ foldr vmask' ([],msk) masks
+ where
+ masks = map (\m -> (m,show m)) [0..toEnum (bitSize msk - 1)] ++
+ [(numLockMask,"num" )
+ ,( lockMask,"lock" )
+ ,(controlMask,"ctrl" )
+ ,( shiftMask,"shift")
+ ,( mod5Mask,"mod5" )
+ ,( mod4Mask,"mod4" )
+ ,( mod3Mask,"mod3" )
+ ,( mod2Mask,"mod2" )
+ ,( mod1Mask,"mod1" )
+ ]
+ vmask' _ a@( _,0) = a
+ vmask' (m,s) (ss,v) | v .&. m == m = (s:ss,v .&. complement m)
+ vmask' _ r = r