aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorValery V. Vorotyntsev <valery.vv@gmail.com>2007-11-12 18:55:30 +0100
committerValery V. Vorotyntsev <valery.vv@gmail.com>2007-11-12 18:55:30 +0100
commit3d0e7fedba6e18dc9e6cf3a97c2eb08e0b224817 (patch)
treedbfb755f73d04fd3d7f911d2773f7b3c22129207 /XMonad
parent538b4acedaf243bea1110aafec9bb2a58877982a (diff)
downloadXMonadContrib-3d0e7fedba6e18dc9e6cf3a97c2eb08e0b224817.tar.gz
XMonadContrib-3d0e7fedba6e18dc9e6cf3a97c2eb08e0b224817.tar.xz
XMonadContrib-3d0e7fedba6e18dc9e6cf3a97c2eb08e0b224817.zip
XMonad.Config.CustomKeys - new module
This module is another key bindings customization helper. Differences from XMonad.Util.EZConfig by Devin Mullins: EZConfig -- M.union/M.difference CustomKeys -- Monad.Reader + foldr'ed M.insert/M.delete IMHO, both modules could evolve into something nice. :) Please discuss at the mailing list. darcs-hash:20071112175530-ae588-abdff35dfe36459867a21d6d181e4c91aab5b0d2.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Config/CustomKeys.hs65
1 files changed, 65 insertions, 0 deletions
diff --git a/XMonad/Config/CustomKeys.hs b/XMonad/Config/CustomKeys.hs
new file mode 100644
index 0000000..8146af8
--- /dev/null
+++ b/XMonad/Config/CustomKeys.hs
@@ -0,0 +1,65 @@
+--------------------------------------------------------------------
+-- |
+-- Module : XMonad.Config.CustomKeys
+-- Copyright : (c) 2007 Valery V. Vorotyntsev
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Valery V. Vorotynsev <valery.vv@gmail.com>
+--
+-- Customized key bindings.
+--
+-- (See also "XMonad.Util.EZConfig" in XMonadContrib.)
+--------------------------------------------------------------------
+
+module XMonad.Config.CustomKeys (
+ -- * Usage
+ -- $usage
+ customKeys
+ ) where
+
+import XMonad
+import Graphics.X11.Xlib
+
+import Control.Monad.Reader
+import qualified Data.Map as M
+
+-- $usage
+--
+-- 1. In @~\/.xmonad\/xmonad.hs@ add:
+--
+-- > import XMonad.Config.CustomKeys
+--
+-- 2. Set key bindings with 'customKeys':
+--
+-- > main = xmonad defaultConfig { 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, shiftMas] [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+")
+-- > ]
+
+-- | XXX comment me (no tautology please)
+customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -- ^ unused shortcuts
+ -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -- ^ new bindings
+ -> XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
+customKeys = (runReader .) . customize
+
+customize :: (XConfig Layout -> [(KeyMask, KeySym)])
+ -> (XConfig Layout -> [((KeyMask, KeySym), X ())])
+ -> Reader (XConfig Layout) (M.Map (KeyMask, KeySym) (X ()))
+customize ds is = Reader (keys defaultConfig) >>= delete ds >>= insert is
+
+delete :: (MonadReader r m, Ord a) => (r -> [a]) -> M.Map a b -> m (M.Map a b)
+delete dels kmap = asks dels >>= return . foldr M.delete kmap
+
+insert :: (MonadReader r m, Ord a) =>
+ (r -> [(a, b)]) -> M.Map a b -> m (M.Map a b)
+insert ins kmap = asks ins >>= return . foldr (uncurry M.insert) kmap