Copyright | Devin Mullins <me@twifkak.com> Brent Yorgey <byorgey@gmail.com> (key parsing) |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Devin Mullins <me@twifkak.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Useful helper functions for amending the default configuration, and for parsing keybindings specified in a special (emacs-like) format.
(See also XMonad.Util.CustomKeys in xmonad-contrib.)
Synopsis
- additionalKeys :: XConfig a -> [((KeyMask, KeySym), X ())] -> XConfig a
- additionalKeysP :: XConfig l -> [(String, X ())] -> XConfig l
- remapKeysP :: XConfig l -> [(String, String)] -> XConfig l
- removeKeys :: XConfig a -> [(KeyMask, KeySym)] -> XConfig a
- removeKeysP :: XConfig l -> [String] -> XConfig l
- additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a
- removeMouseBindings :: XConfig a -> [(ButtonMask, Button)] -> XConfig a
- mkKeymap :: XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ())
- checkKeymap :: XConfig l -> [(String, a)] -> X ()
- mkNamedKeymap :: XConfig l -> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)]
- parseKey :: Parser KeySym
- parseKeyCombo :: XConfig l -> Parser (KeyMask, KeySym)
- parseKeySequence :: XConfig l -> Parser [(KeyMask, KeySym)]
- readKeySequence :: XConfig l -> String -> Maybe (NonEmpty (KeyMask, KeySym))
Usage
To use this module, first import it into your xmonad.hs
:
import XMonad.Util.EZConfig
Then, use one of the provided functions to modify your
configuration. You can use additionalKeys
, removeKeys
,
additionalMouseBindings
, and removeMouseBindings
to easily add
and remove keybindings or mouse bindings. You can use mkKeymap
to create a keymap using emacs-style keybinding specifications
like "M-x"
instead of (modMask, xK_x)
, or additionalKeysP
and removeKeysP
to easily add or remove emacs-style keybindings.
If you use emacs-style keybindings, the checkKeymap
function is
provided, suitable for adding to your startupHook
, which can warn
you of any parse errors or duplicate bindings in your keymap.
For more information and usage examples, see the documentation provided with each exported function, and check the xmonad config archive (http://haskell.org/haskellwiki/Xmonad/Config_archive) for some real examples of use.
Adding or removing keybindings
additionalKeys :: XConfig a -> [((KeyMask, KeySym), X ())] -> XConfig a infixl 4 Source #
Add or override keybindings from the existing set. Example use:
main = xmonad $ def { terminal = "urxvt" } `additionalKeys` [ ((mod1Mask, xK_m ), spawn "echo 'Hi, mom!' | dzen2 -p 4") , ((mod1Mask, xK_BackSpace), withFocused hide) -- N.B. this is an absurd thing to do ]
This overrides the previous definition of mod-m.
Note that, unlike in xmonad 0.4 and previous, you can't use modMask to refer
to the modMask you configured earlier. You must specify mod1Mask (or
whichever), or add your own myModMask = mod1Mask
line.
additionalKeysP :: XConfig l -> [(String, X ())] -> XConfig l infixl 4 Source #
Like additionalKeys
, except using short String
key
descriptors like "M-m"
instead of (modMask, xK_m)
, as
described in the documentation for mkKeymap
. For example:
main = xmonad $ def { terminal = "urxvt" } `additionalKeysP` [ ("M-m", spawn "echo 'Hi, mom!' | dzen2 -p 4") , ("M-<Backspace>", withFocused hide) -- N.B. this is an absurd thing to do ]
remapKeysP :: XConfig l -> [(String, String)] -> XConfig l infixl 4 Source #
Remap keybindings from one binding to another. More precisely, the
input list contains pairs of the form (TO, FROM)
, and maps the
action bound to FROM
to the key TO
. For example, the following
would bind "M-m"
to what's bound to "M-c"
(which is to close the
focused window, in this case):
main :: IO () main = xmonad $ def `remapKeysP` [("M-m", "M-c")]
NOTE: Submaps are not transparent, and thus these keys can't be
accessed in this way: more explicitly, the FROM
string may **not**
be a submap. However, the TO
can be a submap without problems.
This means that
xmonad $ def `remapKeysP` [("M-m", "M-c a")]
is illegal (and indeed will just disregard the binding altogether), while
xmonad $ def `remapKeysP` [("M-c a", "M-m")]
is totally fine.
removeKeys :: XConfig a -> [(KeyMask, KeySym)] -> XConfig a infixl 4 Source #
Remove standard keybindings you're not using. Example use:
main = xmonad $ def { terminal = "urxvt" } `removeKeys` [(mod1Mask .|. shiftMask, n) | n <- [xK_1 .. xK_9]]
removeKeysP :: XConfig l -> [String] -> XConfig l infixl 4 Source #
Like removeKeys
, except using short String
key descriptors
like "M-m"
instead of (modMask, xK_m)
, as described in the
documentation for mkKeymap
. For example:
main = xmonad $ def { terminal = "urxvt" } `removeKeysP` ["M-S-" ++ [n] | n <- ['1'..'9']]
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a infixl 4 Source #
Like additionalKeys
, but for mouse bindings.
removeMouseBindings :: XConfig a -> [(ButtonMask, Button)] -> XConfig a infixl 4 Source #
Like removeKeys
, but for mouse bindings.
Emacs-style keybinding specifications
mkKeymap :: XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ()) Source #
Given a config (used to determine the proper modifier key to use)
and a list of (String, X ())
pairs, create a key map by parsing
the key sequence descriptions contained in the Strings. The key
sequence descriptions are "emacs-style": M-
, C-
, S-
, and
M#-
denote mod, control, shift, and mod1-mod5 (where #
is
replaced by the appropriate number) respectively. Note that if
you want to make a keybinding using 'alt' even though you use a
different key (like the 'windows' key) for 'mod', you can use
something like "M1-x"
for alt+x (check the output of xmodmap
to see which mod key 'alt' is bound to). Some special keys can
also be specified by enclosing their name in angle brackets.
For example, "M-C-x"
denotes mod+ctrl+x; "S-<Escape>"
denotes shift-escape; "M1-C-<Delete>"
denotes alt+ctrl+delete
(assuming alt is bound to mod1, which is common).
Sequences of keys can also be specified by separating the key
descriptions with spaces. For example, "M-x y <Down>"
denotes the
sequence of keys mod+x, y, down. Submaps (see
XMonad.Actions.Submap) will be automatically generated to
correctly handle these cases.
So, for example, a complete key map might be specified as
keys = \c -> mkKeymap c $ [ ("M-S-<Return>", spawn $ terminal c) , ("M-x w", spawn "xmessage 'woohoo!'") -- type mod+x then w to pop up 'woohoo!' , ("M-x y", spawn "xmessage 'yay!'") -- type mod+x then y to pop up 'yay!' , ("M-S-c", kill) ]
Alternatively, you can use additionalKeysP
to automatically
create a keymap and add it to your config.
Here is a complete list of supported special keys. Note that a few keys, such as the arrow keys, have synonyms. If there are other special keys you would like to see supported, feel free to submit a patch, or ask on the xmonad mailing list; adding special keys is quite simple.
<Backspace> <Tab> <Return> <Pause> <Num_Lock> <Caps_Lock> <Scroll_lock> <Sys_Req> <Print> <Escape>, <Esc> <Delete> <Home> <Left>, <L> <Up>, <U> <Right>, <R> <Down>, <D> <Page_Up> <Page_Down> <End> <Insert> <Break> <Space> <Control_L> <Control_R> <Shift_L> <Shift_R> <Alt_L> <Alt_R> <Meta_L> <Meta_R> <Super_L> <Super_R> <Hyper_L> <Hyper_R> <F1>-<F24> <KP_Space> <KP_Tab> <KP_Enter> <KP_F1> <KP_F2> <KP_F3> <KP_F4> <KP_Home> <KP_Left> <KP_Up> <KP_Right> <KP_Down> <KP_Prior> <KP_Page_Up> <KP_Next> <KP_Page_Down> <KP_End> <KP_Begin> <KP_Insert> <KP_Delete> <KP_Equal> <KP_Multiply> <KP_Add> <KP_Separator> <KP_Subtract> <KP_Decimal> <KP_Divide> <KP_0>-<KP_9>
Long list of multimedia keys. Please note that not all keys may be present in your particular setup although most likely they will do.
<XF86ModeLock> <XF86MonBrightnessUp> <XF86MonBrightnessDown> <XF86KbdLightOnOff> <XF86KbdBrightnessUp> <XF86KbdBrightnessDown> <XF86Standby> <XF86AudioLowerVolume> <XF86AudioMute> <XF86AudioRaiseVolume> <XF86AudioPlay> <XF86AudioStop> <XF86AudioPrev> <XF86AudioNext> <XF86HomePage> <XF86Mail> <XF86Start> <XF86Search> <XF86AudioRecord> <XF86Calculator> <XF86Memo> <XF86ToDoList> <XF86Calendar> <XF86PowerDown> <XF86ContrastAdjust> <XF86RockerUp> <XF86RockerDown> <XF86RockerEnter> <XF86Back> <XF86Forward> <XF86Stop> <XF86Refresh> <XF86PowerOff> <XF86WakeUp> <XF86Eject> <XF86ScreenSaver> <XF86WWW> <XF86Sleep> <XF86Favorites> <XF86AudioPause> <XF86AudioMedia> <XF86MyComputer> <XF86VendorHome> <XF86LightBulb> <XF86Shop> <XF86History> <XF86OpenURL> <XF86AddFavorite> <XF86HotLinks> <XF86BrightnessAdjust> <XF86Finance> <XF86Community> <XF86AudioRewind> <XF86XF86BackForward> <XF86Launch0>-<XF86Launch9>, <XF86LaunchA>-<XF86LaunchF> <XF86ApplicationLeft> <XF86ApplicationRight> <XF86Book> <XF86CD> <XF86Calculater> <XF86Clear> <XF86Close> <XF86Copy> <XF86Cut> <XF86Display> <XF86DOS> <XF86Documents> <XF86Excel> <XF86Explorer> <XF86Game> <XF86Go> <XF86iTouch> <XF86LogOff> <XF86Market> <XF86Meeting> <XF86MenuKB> <XF86MenuPB> <XF86MySites> <XF86New> <XF86News> <XF86OfficeHome> <XF86Open> <XF86Option> <XF86Paste> <XF86Phone> <XF86Q> <XF86Reply> <XF86Reload> <XF86RotateWindows> <XF86RotationPB> <XF86RotationKB> <XF86Save> <XF86ScrollUp> <XF86ScrollDown> <XF86ScrollClick> <XF86Send> <XF86Spell> <XF86SplitScreen> <XF86Support> <XF86TaskPane> <XF86Terminal> <XF86Tools> <XF86Travel> <XF86UserPB> <XF86User1KB> <XF86User2KB> <XF86Video> <XF86WheelButton> <XF86Word> <XF86Xfer> <XF86ZoomIn> <XF86ZoomOut> <XF86Away> <XF86Messenger> <XF86WebCam> <XF86MailForward> <XF86Pictures> <XF86Music> <XF86TouchpadToggle> <XF86AudioMicMute> <XF86_Switch_VT_1>-<XF86_Switch_VT_12> <XF86_Ungrab> <XF86_ClearGrab> <XF86_Next_VMode> <XF86_Prev_VMode> <XF86Bluetooth>
checkKeymap :: XConfig l -> [(String, a)] -> X () Source #
Given a configuration record and a list of (key sequence
description, action) pairs, check the key sequence descriptions
for validity, and warn the user (via a popup xmessage window) of
any unparseable or duplicate key sequences. This function is
appropriate for adding to your startupHook
, and you are highly
encouraged to do so; otherwise, duplicate or unparseable
keybindings will be silently ignored.
For example, you might do something like this:
main = xmonad $ myConfig myKeymap = [("S-M-c", kill), ...] myConfig = def { ... keys = \c -> mkKeymap c myKeymap startupHook = return () >> checkKeymap myConfig myKeymap ... }
NOTE: the return ()
in the example above is very important!
Otherwise, you might run into problems with infinite mutual
recursion: the definition of myConfig depends on the definition of
startupHook, which depends on the definition of myConfig, ... and
so on. Actually, it's likely that the above example in particular
would be OK without the return ()
, but making myKeymap
take
myConfig
as a parameter would definitely lead to
problems. Believe me. It, uh, happened to my friend. In... a
dream. Yeah. In any event, the return () >>
introduces enough
laziness to break the deadlock.
mkNamedKeymap :: XConfig l -> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)] Source #
Parsers
parseKeyCombo :: XConfig l -> Parser (KeyMask, KeySym) Source #
Parse a modifier-key combination such as "M-C-s" (mod+ctrl+s).