aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/CustomKeys.hs
diff options
context:
space:
mode:
authorValery V. Vorotyntsev <valery.vv@gmail.com>2007-11-14 16:34:18 +0100
committerValery V. Vorotyntsev <valery.vv@gmail.com>2007-11-14 16:34:18 +0100
commitfe55d0845c351e8ca15dcb4aade79fbda671f221 (patch)
tree8c056699d85d8b9eaed7e6fd348eb2b630f8b17f /XMonad/Util/CustomKeys.hs
parentfe7c8a905033464f768af4c7223c7977e8e0211d (diff)
downloadXMonadContrib-fe55d0845c351e8ca15dcb4aade79fbda671f221.tar.gz
XMonadContrib-fe55d0845c351e8ca15dcb4aade79fbda671f221.tar.xz
XMonadContrib-fe55d0845c351e8ca15dcb4aade79fbda671f221.zip
CustomKeys.hs: moved into `Util' directory
I still wonder why do we need all those configuration examples. :) darcs-hash:20071114153418-ae588-f5280e0c2f0de7aebec97b81f934b2529aba4f0f.gz
Diffstat (limited to 'XMonad/Util/CustomKeys.hs')
-rw-r--r--XMonad/Util/CustomKeys.hs76
1 files changed, 76 insertions, 0 deletions
diff --git a/XMonad/Util/CustomKeys.hs b/XMonad/Util/CustomKeys.hs
new file mode 100644
index 0000000..7c7a239
--- /dev/null
+++ b/XMonad/Util/CustomKeys.hs
@@ -0,0 +1,76 @@
+--------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.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 xmonad-contrib.)
+--------------------------------------------------------------------
+
+module XMonad.Util.CustomKeys (
+ -- * Usage
+ -- $usage
+ customKeys
+ , customKeysFrom
+ ) 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.Util.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+")
+-- > ]
+
+-- | Customize 'XMonad.Config.defaultConfig' -- delete needless
+-- shortcuts and insert those you will use.
+customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -- ^ shortcuts to delete
+ -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -- ^ key bindings to insert
+ -> XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
+customKeys = customKeysFrom defaultConfig
+
+-- | General variant of 'customKeys': customize key bindings of
+-- third-party configuration.
+customKeysFrom :: XConfig l -- ^ original configuration
+ -> (XConfig Layout -> [(KeyMask, KeySym)]) -- ^ shortcuts to delete
+ -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -- ^ key bindings to insert
+ -> XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
+customKeysFrom conf = (runReader .) . customize conf
+
+customize :: XConfig l
+ -> (XConfig Layout -> [(KeyMask, KeySym)])
+ -> (XConfig Layout -> [((KeyMask, KeySym), X ())])
+ -> Reader (XConfig Layout) (M.Map (KeyMask, KeySym) (X ()))
+customize conf ds is = Reader (keys conf) >>= 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