xmonad-contrib-0.9.1: Third party extensions for xmonad

Portabilityunportable
Stabilityunstable
MaintainerAdam Vogt <vogt.adam@gmail.com>

XMonad.Util.NamedActions

Contents

Description

A wrapper for keybinding configuration that can list the available keybindings.

Synopsis

Usage:

Here is an example config that demonstrates the usage of sendMessage', mkNamedKeymap, addDescrKeys, and ^++^

 import XMonad
 import XMonad.Util.NamedActions
 import XMonad.Util.EZConfig

 main = xmonad $ addDescrKeys ((mod4Mask, xK_F1), xMessage) myKeys
                    defaultConfig { modMask = mod4Mask }

 myKeys c = (subtitle "Custom Keys":) $ mkNamedKeymap c $
    [("M-x a", addName "useless message" $ spawn "xmessage foo"),
     ("M-c", sendMessage' Expand)]
     ^++^
    [("<XF86AudioPlay>", spawn "mpc toggle" :: X ()),
     ("<XF86AudioNext>", spawn "mpc next")]

Using ^++^, you can combine bindings whose actions are X () as well as actions that have descriptions. However you cannot mix the two in a single list, unless each is prefixed with addName or noName.

If you don't like EZConfig, you can still use ^++^ with the basic XMonad keybinding configuration too.

Also note the unfortunate necessity of a type annotation, since spawn is too general.

sendMessage' :: (Message a, Show a) => a -> NamedActionSource

sendMessage but add a description that is show message. Note that not all messages have show instances.

spawn' :: String -> NamedActionSource

spawn but the description is the string passed

submapName :: HasName a => [((KeyMask, KeySym), a)] -> NamedActionSource

submap, but propagate the descriptions of the actions. Does this belong in XMonad.Actions.Submap?

addDescrKeys :: (HasName b1, HasName b) => ((KeyMask, KeySym), [((KeyMask, KeySym), NamedAction)] -> b) -> (XConfig Layout -> [((KeyMask, KeySym), b1)]) -> XConfig l -> XConfig lSource

Merge the supplied keys with defaultKeysDescr, also adding a keybinding to run an action for showing the keybindings.

xMessage :: [((KeyMask, KeySym), NamedAction)] -> NamedActionSource

An action to send to addDescrKeys for showing the keybindings. See also showKm and showKmSimple

noName :: X () -> NamedActionSource

These are just the NamedAction constructor but with a more specialized type, so that you don't have to supply any annotations, for ex coercing spawn to X () from the more general MonadIO m => m ()

separator :: ((KeyMask, KeySym), NamedAction)Source

For a prettier presentation: keymask, keysym of 0 are reserved for this purpose: they do not happen, afaik, and keysymToString 0 would raise an error otherwise

(^++^) :: (HasName b, HasName b1) => [(d, b)] -> [(d, b1)] -> [(d, NamedAction)]Source

Combine keymap lists with actions that may or may not have names

data NamedAction Source

An existential wrapper so that different types can be combined in lists, and maps

Constructors

forall a . HasName a => NamedAction a 

defaultKeysDescr :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)]Source

A version of the default keys from XMonad.Config.defaultConfig, but with NamedAction instead of X ()