xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyright(c) 2018 L. S. Leary
LicenseBSD3-style (see LICENSE)
MaintainerYecine Megdiche <yecine.megdiche@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Hooks.Modal

Description

This module implements modal keybindings for xmonad.

Synopsis

Usage

This module provides modal keybindings in xmonad. If you're not familiar with modal keybindings from Vim, you can think of modes as submaps from XMonad.Actions.Submap, but after each action you execute, you land back in the submap until you explicitly exit the submap. To use this module you should apply the modal function to the config, which will setup the list of modes (or rather, XConfig Layout -> Mode) you provide:

import XMonad
import XMonad.Hooks.Modal
import XMonad.Util.EZConfig
import qualified Data.Map as M

main :: IO ()
main =
  xmonad
    . modal [noModMode, floatMode 10, overlayedFloatMode 10, sayHelloMode]
    $ def
    `additionalKeysP` [ ("M-S-n", setMode noModModeLabel)
                      , ("M-S-r", setMode floatModeLabel)
                      , ("M-S-z", setMode overlayedFloatModeLabel)
                      , ("M-S-h", setMode "Hello")
                      ]

sayHelloMode :: Mode
sayHelloMode = mode "Hello" $ mkKeysEz
  [ ("h", xmessage "Hello, World!")
  , ("M-g", xmessage "Goodbye, World!")
  ]

Alternatively, one could have defined sayHelloMode as

sayHelloMode :: Mode
sayHelloMode = mode "Hello" $ \cfg ->
  M.fromList [ ((noModMask, xK_h), xmessage "Hello, World!")
             , ((modMask cfg, xK_g), xmessage "Goodbye, World!")
             ]

In short, a Mode has a label describing its purpose, as well as attached keybindings. These are of the form

  • [(String, X ())], or
  • XConfig Layout -> M.Map (ButtonMask, KeySym) (X ()).

The former—accessible via mkKeysEz—is how specifying keys work with XMonad.Util.EZConfig, while the latter is more geared towards how defining keys works by default in xmonad. Note that, by default, modes are exited with the Escape key. If one wishes to customise this, the modeWithExit function should be used instead of mode when defining a new mode.

The label of the active mode can be logged with logMode to be displayed in a status bar, for example (For more information check XMonad.Util.Loggers). Some examples are included in the provided modes.

modal :: [Mode] -> XConfig l -> XConfig l Source #

Adds the provided modes to the user's config, and sets up the bells and whistles needed for them to work.

modeWithExit :: String -> String -> (XConfig Layout -> Map (KeyMask, KeySym) (X ())) -> Mode Source #

Create a Mode from the given binding to exitMode, label and keybindings.

mode :: String -> (XConfig Layout -> Map (KeyMask, KeySym) (X ())) -> Mode Source #

Create a Mode from the given label and keybindings. Sets the escape key to exitMode.

data Mode Source #

The mode type. Use mode or modeWithExit to create modes.

mkKeysEz :: [(String, X ())] -> XConfig Layout -> Map (ButtonMask, KeySym) (X ()) Source #

From a list of XMonad.Util.EZConfig-style bindings, generate a key representation.

>>> mkKeysEz [("h", xmessage "Hello, world!")]

setMode :: String -> X () Source #

Set the current Mode based on its label.

exitMode :: X () Source #

Exits the current mode.

Provided Modes

noModMode :: Mode Source #

In this Mode, all keybindings are available without the need for pressing the modifier. Pressing escape exits the mode.

floatMode Source #

Arguments

:: Int

Step size

-> Mode 

A mode to control floating windows with {hijk}, M-{hijk} and M-S-{hijk} in order to respectively move, enlarge and shrink windows.

overlayedFloatMode Source #

Arguments

:: Int

Step size

-> Mode 

Similar to resizeMode, but keeps the bindings of the original config active.

floatMap Source #

Arguments

:: KeyMask

Move mask

-> KeyMask

Enlarge mask

-> KeyMask

Shrink mask

-> Int

Step size

-> Map (ButtonMask, KeySym) (X ()) 

Generates the keybindings for floatMode and overlayedFloatMode.

overlay Source #

Arguments

:: String

Label for the new mode

-> Mode

Base mode

-> Mode 

Modifies a mode so that the keybindings are merged with those from the config instead of replacing them.

Logger

logMode :: Logger Source #

A Logger to display the current mode.