xmonad-contrib-0.18.1: Community-maintained extensions for xmonad
Copyright(c) Jason Creighton <jcreigh@gmail.com>
LicenseBSD3-style (see LICENSE)
MaintainerJason Creighton <jcreigh@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Actions.Submap

Description

A module that allows the user to create a sub-mapping of key bindings.

Synopsis

Usage

First, import this module into your xmonad.hs:

import XMonad.Actions.Submap

Allows you to create a sub-mapping of keys. Example:

   , ((modm, xK_a), submap . M.fromList $
       [ ((0, xK_n),     spawn "mpc next")
       , ((0, xK_p),     spawn "mpc prev")
       , ((0, xK_z),     spawn "mpc random")
       , ((0, xK_space), spawn "mpc toggle")
       ])

So, for example, to run 'spawn "mpc next"', you would hit mod-a (to trigger the submapping) and then n to run that action. (0 means "no modifier"). You are, of course, free to use any combination of modifiers in the submapping. However, anyModifier will not work, because that is a special value passed to XGrabKey() and not an actual modifier.

For detailed instructions on editing your key bindings, see the tutorial.

submap :: Map (KeyMask, KeySym) (X ()) -> X () Source #

Given a Map from key bindings to X () actions, return an action which waits for a user keypress and executes the corresponding action, or does nothing if the key is not found in the map.

visualSubmap Source #

Arguments

:: WindowConfig

The config for the spawned window.

-> Map (KeyMask, KeySym) (String, X ())

A map keybinding -> (description, action).

-> X () 

Like submap, but visualise the relevant options.

Example

Expand
import qualified Data.Map as Map
import XMonad.Actions.Submap

gotoLayout :: [(String, X ())]   -- for use with EZConfig
gotoLayout =  -- assumes you have a layout named "Tall" and one named "Full".
  [("M-l", visualSubmap def $ Map.fromList $ map (\(k, s, a) -> ((0, k), (s, a)))
             [ (xK_t, "Tall", switchToLayout "Tall")     -- "M-l t" switches to "Tall"
             , (xK_r, "Full", switchToLayout "Full")     -- "M-l r" switches to "full"
             ])]

One could alternatively also write gotoLayout as

gotoLayout = [("M-l", visualSubmap def $ Map.fromList $
                        [ ((0, xK_t), subName "Tall" $ switchToLayout "Tall")
                        , ((0, xK_r), subName "Full" $ switchToLayout "Full")
                        ])]

visualSubmapSorted Source #

Arguments

:: ([((KeyMask, KeySym), String)] -> [((KeyMask, KeySym), String)])

A function to resort the descriptions

-> WindowConfig

The config for the spawned window.

-> Map (KeyMask, KeySym) (String, X ())

A map keybinding -> (description, action).

-> X () 

Like visualSubmap, but is able to sort the descriptions. For example,

import Data.Ord (comparing, Down)

visualSubmapSorted (sortBy (comparing Down)) def

would sort the (key, description) pairs by their keys in descending order.

submapDefault :: X () -> Map (KeyMask, KeySym) (X ()) -> X () Source #

Like submap, but executes a default action if the key did not match.

submapDefaultWithKey :: ((KeyMask, KeySym) -> X ()) -> Map (KeyMask, KeySym) (X ()) -> X () Source #

Like submapDefault, but sends the unmatched key to the default action as argument.

Utilities

subName :: String -> X () -> (String, X ()) Source #

Give a name to an action.