| Copyright | (c) 2007 Valery V. Vorotyntsev | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | Valery V. Vorotynsev <valery.vv@gmail.com> | 
| Safe Haskell | None | 
| Language | Haskell98 | 
XMonad.Util.CustomKeys
Contents
Description
Customized key bindings.
(See also XMonad.Util.EZConfig in xmonad-contrib.)
- customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
- customKeysFrom :: XConfig l -> (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
Usage
- In ~/.xmonad/xmonad.hsadd:
import XMonad.Util.CustomKeys
- Set key bindings with customKeys:
main = xmonad def { keys = customKeys delkeys inskeys }
    where
      delkeys :: XConfig l -> [(KeyMask, KeySym)]
      delkeys XConfig {modMask = modm} =
          -- we're preferring Futurama to Xinerama here
          [ (modm .|. m, k) | (m, k) <- zip [0, shiftMask] [xK_w, xK_e, xK_r] ]
      inskeys :: XConfig l -> [((KeyMask, KeySym), X ())]
      inskeys conf@(XConfig {modMask = modm}) =
          [ ((mod1Mask,             xK_F2  ), spawn $ terminal conf)
          , ((modm .|. controlMask, xK_F11 ), spawn "xscreensaver-command -lock")
          , ((mod1Mask,             xK_Down), spawn "amixer set Master 1-")
          , ((mod1Mask,             xK_Up  ), spawn "amixer set Master 1+")
          ]0 (hidden feature). You can always replace bindings map entirely. No need to import CustomKeys this time:
import XMonad
import System.Exit
import qualified Data.Map as M
main = xmonad def {
         keys = \_ -> M.fromList [
                 -- Let me out of here! I want my KDE back! Help! Help!
                 ( (0, xK_Escape), io (exitWith ExitSuccess) ) ] }Arguments
| :: (XConfig Layout -> [(KeyMask, KeySym)]) | shortcuts to delete | 
| -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) | key bindings to insert | 
| -> XConfig Layout | |
| -> Map (KeyMask, KeySym) (X ()) | 
Customize def -- delete needless
 shortcuts and insert those you will use.
Arguments
| :: XConfig l | original configuration | 
| -> (XConfig Layout -> [(KeyMask, KeySym)]) | shortcuts to delete | 
| -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) | key bindings to insert | 
| -> XConfig Layout | |
| -> Map (KeyMask, KeySym) (X ()) | 
General variant of customKeys: customize key bindings of
 third-party configuration.