| Copyright | 2009 Adam Vogt <vogt.adam@gmail.com> | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | Adam Vogt <vogt.adam@gmail.com> | 
| Stability | unstable | 
| Portability | unportable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
XMonad.Util.NamedActions
Contents
Description
A wrapper for keybinding configuration that can list the available keybindings.
Note that xmonad>=0.11 has by default a list of the default keybindings
 bound to M-S-/ or M-?.
- sendMessage' :: (Message a, Show a) => a -> NamedAction
- spawn' :: String -> NamedAction
- submapName :: HasName a => [((KeyMask, KeySym), a)] -> NamedAction
- addDescrKeys :: (HasName b1, HasName b) => ((KeyMask, KeySym), [((KeyMask, KeySym), NamedAction)] -> b) -> (XConfig Layout -> [((KeyMask, KeySym), b1)]) -> XConfig l -> XConfig l
- addDescrKeys' :: HasName b => ((KeyMask, KeySym), [((KeyMask, KeySym), NamedAction)] -> b) -> (XConfig Layout -> [((KeyMask, KeySym), NamedAction)]) -> XConfig l -> XConfig l
- xMessage :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
- showKmSimple :: [((KeyMask, KeySym), NamedAction)] -> [[Char]]
- showKm :: [((KeyMask, KeySym), NamedAction)] -> [String]
- noName :: X () -> NamedAction
- oneName :: (X (), String) -> NamedAction
- addName :: String -> X () -> NamedAction
- separator :: ((KeyMask, KeySym), NamedAction)
- subtitle :: String -> ((KeyMask, KeySym), NamedAction)
- (^++^) :: (HasName b, HasName b1) => [(d, b)] -> [(d, b1)] -> [(d, NamedAction)]
- data NamedAction = forall a . HasName a => NamedAction a
- class HasName a
- defaultKeysDescr :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)]
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
                   def { 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 -> NamedAction Source
sendMessage but add a description that is show message. Note that not
 all messages have show instances.
spawn' :: String -> NamedAction Source
spawn but the description is the string passed
submapName :: HasName a => [((KeyMask, KeySym), a)] -> NamedAction Source
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 l Source
Merge the supplied keys with defaultKeysDescr, also adding a keybinding
 to run an action for showing the keybindings.
addDescrKeys' :: HasName b => ((KeyMask, KeySym), [((KeyMask, KeySym), NamedAction)] -> b) -> (XConfig Layout -> [((KeyMask, KeySym), NamedAction)]) -> XConfig l -> XConfig l Source
Without merging with defaultKeysDescr
xMessage :: [((KeyMask, KeySym), NamedAction)] -> NamedAction Source
An action to send to addDescrKeys for showing the keybindings. See also showKm and showKmSimple
showKmSimple :: [((KeyMask, KeySym), NamedAction)] -> [[Char]] Source
noName :: X () -> NamedAction Source
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 ()
oneName :: (X (), String) -> NamedAction Source
addName :: String -> X () -> NamedAction Source
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 | 
Instances
Minimal complete definition
getAction
defaultKeysDescr :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)] Source
A version of the default keys from the default configuration, but with
 NamedAction  instead of X ()