aboutsummaryrefslogtreecommitdiffstats
path: root/Submap.hs
blob: 987ff46ce6d4e6a5da1a9b9856734ec04aa2336b (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
{-
Allows you to create a sub-mapping of keys. Example:

    , ((modMask, xK_a), submap . M.fromList $
        [ ((0, xK_n),     spawn "mpc next")
        , ((0, xK_p),     spawn "mpc prev")
        , ((0, xK_z),     spawn "mpc random")
        , ((0, xK_space), spawn "mpc toggle")
        ])

So, for example, to run 'spawn "mpc next"', you would hit mod-a (to trigger the
submapping) and then 'n' to run that action. (0 means "no modifier"). You are,
of course, free to use any combination of modifiers in the submapping. However,
anyModifier will not work, because that is a special value passed to XGrabKey()
and not an actual modifier.
-}

module XMonadContrib.Submap where

import Control.Monad.Reader

import XMonad
import Operations (cleanMask)
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import qualified Data.Map as M

submap :: M.Map (KeyMask, KeySym) (X ()) -> X ()
submap keys = do
    XConf { theRoot = root, display = d } <- ask

    io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime

    keyspec <- 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 return (cleanMask m, keysym)

    io $ ungrabKeyboard d currentTime

    whenJust (M.lookup keyspec keys) id