Merge pull request #515 from slotThe/ezmotion

X.A.EasyMotion: Cleanup, doc improvement
This commit is contained in:
slotThe
2021-04-26 08:16:05 +02:00
committed by GitHub

View File

@@ -14,19 +14,22 @@
-- Provides functionality to use key chords to focus a visible window. Overlays a unique key chord -- Provides functionality to use key chords to focus a visible window. Overlays a unique key chord
-- (a string) above each visible window and allows the user to select a window by typing that -- (a string) above each visible window and allows the user to select a window by typing that
-- chord. -- chord.
-- Inspired by https://github.com/easymotion/vim-easymotion. -- Inspired by <https://github.com/easymotion/vim-easymotion vim-easymotion>.
-- Thanks to Tom Hinton (https://github.com/larkery) for some feature inspiration and window -- Thanks to <https://github.com/larkery Tom Hinton> for some feature inspiration and window
-- sorting code. -- sorting code.
-- --
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Actions.EasyMotion ( module XMonad.Actions.EasyMotion ( -- * Usage
-- * Usage
-- $usage -- $usage
selectWindow selectWindow
, def
-- * Configuration
, EasyMotionConfig(..) , EasyMotionConfig(..)
, ChordKeys(..) , ChordKeys(..)
, def
-- * Creating overlays
, fullSize , fullSize
, fixedSize , fixedSize
, textSize , textSize
@@ -40,8 +43,9 @@ import XMonad.Util.Font (releaseXMF, initXMF, Align(AlignCente
import XMonad.Util.XUtils (fi, createNewWindow, paintAndWrite, deleteWindow, showWindow) import XMonad.Util.XUtils (fi, createNewWindow, paintAndWrite, deleteWindow, showWindow)
import Control.Monad (replicateM) import Control.Monad (replicateM)
import Control.Arrow ((&&&)) import Control.Arrow ((&&&))
import Data.Maybe (isJust) import Data.Functor (($>))
import qualified Data.Map.Strict as M (Map, map, foldr, mapWithKey) import Data.Maybe (isJust, listToMaybe)
import qualified Data.Map.Strict as M (Map, map, mapWithKey, elems)
import Data.Set (toList) import Data.Set (toList)
import Graphics.X11.Xlib.Extras (getWindowAttributes, getEvent) import Graphics.X11.Xlib.Extras (getWindowAttributes, getEvent)
import qualified Data.List as L (filter, partition, find, nub) import qualified Data.List as L (filter, partition, find, nub)
@@ -49,7 +53,8 @@ import Data.List (sortOn)
-- $usage -- $usage
-- --
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module's basic functionality with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- --
-- > import XMonad.Actions.EasyMotion (selectWindow) -- > import XMonad.Actions.EasyMotion (selectWindow)
-- --
@@ -57,55 +62,56 @@ import Data.List (sortOn)
-- --
-- > import XMonad.Actions.EasyMotion (selectWindow, EasyMotionConfig(..)) -- > import XMonad.Actions.EasyMotion (selectWindow, EasyMotionConfig(..))
-- --
-- Then add a keybinding and an action to the selectWindow function. In this case M-f to focus: -- Then add a keybinding and an action to the 'selectWindow' function.
-- In this case @M-f@ to focus the selected window:
-- --
-- > , ((modm, xK_f), (selectWindow def) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), selectWindow def >>= (`whenJust` windows . W.focusWindow))
-- --
-- Similarly, to kill a window with M-f: -- Similarly, to kill a window with @M-f@:
-- --
-- > , ((modm, xK_f), (selectWindow def) >>= (flip whenJust killWindow)) -- > , ((modm, xK_f), selectWindow def >>= (`whenJust` killWindow))
-- --
-- See 'EasyMotionConfig' for all configuration options. A short summary follows. -- See 'EasyMotionConfig' for all configuration options. A short summary follows.
-- --
-- Default chord keys are s,d,f,j,k,l. To customise these and display options assign -- Default chord keys are @s,d,f,j,k,l@. To customise these and display options assign
-- different values to def: -- different values to 'def' (the default configuration):
-- --
-- > , ((modm, xK_f), (selectWindow def {sKeys = AnyKeys [xK_f, xK_d]}) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{sKeys = AnyKeys [xK_f, xK_d]}) >>= (`whenJust` windows . W.focusWindow))
-- --
-- You must supply at least two different keys in the sKeys list. Keys provided earlier in the list -- You must supply at least two different keys in the 'sKeys' list. Keys provided earlier in the list
-- will be used preferentially- therefore, keys you would like to use more frequently should be -- will be used preferentiallytherefore, keys you would like to use more frequently should be
-- earlier in the list. -- earlier in the list.
-- --
-- To map different sets of keys to different screens. The following configuration maps keys fdsa -- To map different sets of keys to different screens. The following configuration maps keys @fdsa@
-- to screen 0 and hjkl to screen 1. Keys provided earlier in the list will be used preferentially. -- to screen 0 and @hjkl@ to screen 1. Keys provided earlier in the list will be used preferentially.
-- Providing the same key for multiple screens is possible but will break down in some scenarios. -- Providing the same key for multiple screens is possible but will break down in some scenarios.
-- --
-- > import qualified Data.Map.Strict as StrictMap (fromList) -- > import qualified Data.Map.Strict as StrictMap (fromList)
-- > emConf :: EasyMotionConfig -- > emConf :: EasyMotionConfig
-- > emConf = def { sKeys = PerScreenKeys $ StrictMap.fromList [(0, [xK_f, xK_d, xK_s, xK_a]), (1, [xK_h, xK_j, xK_k, xK_l])] } -- > emConf = def { sKeys = PerScreenKeys $ StrictMap.fromList [(0, [xK_f, xK_d, xK_s, xK_a]), (1, [xK_h, xK_j, xK_k, xK_l])] }
-- > -- key bindings -- > -- key bindings
-- > , ((modm, xK_f), (selectWindow emConf) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), selectWindow emConf >>= (`whenJust` windows . W.focusWindow))
-- --
-- To customise the font: -- To customise the font:
-- --
-- > , ((modm, xK_f), (selectWindow def {emFont = "xft: Sans-40"}) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{emFont = "xft: Sans-40"}) >>= (`whenJust` windows . W.focusWindow))
-- --
-- The @emFont@ field provided is supplied directly to the initXMF function. The default is -- The 'emFont' field provided is supplied directly to the 'initXMF' function. The default is
-- "xft:Sans-100". Some example options: -- @"xft:Sans-100"@. Some example options:
-- --
-- > "xft: Sans-40" -- > "xft: Sans-40"
-- > "xft: Arial-100" -- > "xft: Arial-100"
-- > "xft: Cambria-80" -- > "xft: Cambria-80"
-- --
-- Customise the overlay by supplying a function to do so. The signature is @'Position' -> -- Customise the overlay by supplying a function to 'overlayF'. The signature is
-- 'Rectangle' -> 'X' 'Rectangle'@. The parameters are the height in pixels of the selection chord -- @'Position' -> 'Rectangle' -> 'Rectangle'@. The parameters are the height in pixels of
-- and the rectangle of the window to be overlaid. Some are provided: -- the selection chord and the rectangle of the window to be overlaid. Some are provided:
-- --
-- > import XMonad.Actions.EasyMotion (selectWindow, EasyMotionConfig(..), proportional, bar, fullSize) -- > import XMonad.Actions.EasyMotion (selectWindow, EasyMotionConfig(..), proportional, bar, fullSize)
-- > , ((modm, xK_f), (selectWindow def { overlayF = proportional 0.3 }) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{ overlayF = proportional 0.3 }) >>= (`whenJust` windows . W.focusWindow))
-- > , ((modm, xK_f), (selectWindow def { overlayF = bar 0.5 }) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{ overlayF = bar 0.5 }) >>= (`whenJust` windows . W.focusWindow))
-- > , ((modm, xK_f), (selectWindow def { overlayF = fullSize }) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{ overlayF = fullSize }) >>= (`whenJust` windows . W.focusWindow))
-- > , ((modm, xK_f), (selectWindow def { overlayF = fixedSize 300 350 }) >>= (flip whenJust (windows . W.focusWindow))) -- > , ((modm, xK_f), (selectWindow def{ overlayF = fixedSize 300 350 }) >>= (`whenJust` windows . W.focusWindow))
-- TODO: -- TODO:
-- - An overlay function that creates an overlay a proportion of the width XOR height of the -- - An overlay function that creates an overlay a proportion of the width XOR height of the
@@ -146,44 +152,44 @@ import Data.List (sortOn)
-- | Associates a user window, an overlay window created by this module and a rectangle -- | Associates a user window, an overlay window created by this module and a rectangle
-- circumscribing these windows -- circumscribing these windows
data OverlayWindow = data OverlayWindow =
OverlayWindow { win :: Window -- ^ The window managed by xmonad OverlayWindow { win :: !Window -- ^ The window managed by xmonad
, attrs :: WindowAttributes -- ^ Window attributes for @win@ , attrs :: !WindowAttributes -- ^ Window attributes for @win@
, overlay :: Window -- ^ Our window used to display the overlay , overlay :: !Window -- ^ Our window used to display the overlay
, rect :: Rectangle -- ^ The rectangle of @overlay@ , rect :: !Rectangle -- ^ The rectangle of @overlay@
} }
-- | An overlay window and the chord used to select it -- | An overlay window and the chord used to select it
data Overlay = data Overlay =
Overlay { overlayWin :: OverlayWindow -- ^ The window managed by xmonad Overlay { overlayWin :: !OverlayWindow -- ^ The window managed by xmonad
, chord :: [KeySym] -- ^ The chord we'll display in the overlay , chord :: ![KeySym] -- ^ The chord we'll display in the overlay
} }
-- | Maps keys to windows. AnyKeys maps keys to windows regardless which screen they're on. -- | Maps keys to windows. 'AnyKeys' maps keys to windows regardless which screen they're on.
-- PerScreenKeys maps keys to screens to windows. See $usage for more examples. -- 'PerScreenKeys' maps keys to screens to windows. See @Usage@ for more examples.
data ChordKeys = AnyKeys [KeySym] data ChordKeys = AnyKeys ![KeySym]
| PerScreenKeys (M.Map ScreenId [KeySym]) | PerScreenKeys !(M.Map ScreenId [KeySym])
-- | Configuration options for EasyMotion. -- | Configuration options for EasyMotion.
-- --
-- All colors are hex strings, e.g. "#000000" -- All colors are hex strings, e.g. "#000000"
-- --
-- If the number of windows for which chords are required exceeds maxChordLen, chords -- If the number of windows for which chords are required exceeds 'maxChordLen', chords
-- will simply not be generated for these windows. In this way, single-key selection may be -- will simply not be generated for these windows. In this way, single-key selection may be
-- preferred over the ability to select any window. -- preferred over the ability to select any window.
-- --
-- @cancelKey@, @xK_BackSpace@ and any duplicates will be removed from @sKeys@ if included. -- 'cancelKey', @xK_BackSpace@ and any duplicates will be removed from 'sKeys' if included.
-- See usage for examples of @sKeys@. -- See @Usage@ for examples of 'sKeys'.
data EasyMotionConfig = data EasyMotionConfig =
EMConf { txtCol :: String -- ^ Color of the text displayed EMConf { txtCol :: !String -- ^ Color of the text displayed
, bgCol :: String -- ^ Color of the window overlaid , bgCol :: !String -- ^ Color of the window overlaid
, overlayF :: Position -> Rectangle -> Rectangle -- ^ Function to generate overlay rectangle , overlayF :: !(Position -> Rectangle -> Rectangle) -- ^ Function to generate overlay rectangle
, borderCol :: String -- ^ Color of the overlay window borders , borderCol :: !String -- ^ Color of the overlay window borders
, sKeys :: ChordKeys -- ^ Keys to use for window selection , sKeys :: !ChordKeys -- ^ Keys to use for window selection
, cancelKey :: KeySym -- ^ Key to use to cancel selection , cancelKey :: !KeySym -- ^ Key to use to cancel selection
, emFont :: String -- ^ Font for selection characters (passed to initXMF) , emFont :: !String -- ^ Font for selection characters (passed to 'initXMF')
, borderPx :: Int -- ^ Width of border in pixels , borderPx :: !Int -- ^ Width of border in pixels
, maxChordLen :: Int -- ^ Maximum chord length. Use 0 for no maximum. , maxChordLen :: !Int -- ^ Maximum chord length. Use 0 for no maximum.
} }
instance Default EasyMotionConfig where instance Default EasyMotionConfig where
@@ -265,11 +271,11 @@ handleSelectWindow c = do
PerScreenKeys m -> PerScreenKeys m ->
fmap concat fmap concat
$ sequence $ sequence
$ M.foldr (:) [] $ M.elems
$ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m $ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
where where
screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail) screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
screenById sid = L.find ((== sid) . screen) (W.current ws : W.visible ws) screenById sid = L.find ((== sid) . screen) (W.screens ws)
visibleWindowsOnScreen :: ScreenId -> [Window] visibleWindowsOnScreen :: ScreenId -> [Window]
visibleWindowsOnScreen sid = L.filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace visibleWindowsOnScreen sid = L.filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
sortedOverlayWindows :: ScreenId -> X [OverlayWindow] sortedOverlayWindows :: ScreenId -> X [OverlayWindow]
@@ -286,12 +292,12 @@ handleSelectWindow c = do
-- focus the selected window -- focus the selected window
Selected o -> return . Just . win . overlayWin $ o Selected o -> return . Just . win . overlayWin $ o
-- return focus correctly -- return focus correctly
_ -> whenJust (W.peek ws) (windows . W.focusWindow) >> return Nothing _ -> whenJust (W.peek ws) (windows . W.focusWindow) $> Nothing
else releaseXMF f >> return Nothing else releaseXMF f $> Nothing
where where
allKeys :: ChordKeys -> [KeySym] allKeys :: ChordKeys -> [KeySym]
allKeys (AnyKeys ks) = ks allKeys (AnyKeys ks) = ks
allKeys (PerScreenKeys m) = concat $ M.foldr (:) [] m allKeys (PerScreenKeys m) = concat $ M.elems m
buildOverlays :: [KeySym] -> [OverlayWindow] -> [Overlay] buildOverlays :: [KeySym] -> [OverlayWindow] -> [Overlay]
buildOverlays ks = appendChords (maxChordLen c) ks buildOverlays ks = appendChords (maxChordLen c) ks
@@ -323,7 +329,7 @@ selectWindow :: EasyMotionConfig -> X (Maybe Window)
selectWindow conf = selectWindow conf =
handleSelectWindow conf { sKeys = sanitiseKeys (sKeys conf) } handleSelectWindow conf { sKeys = sanitiseKeys (sKeys conf) }
where where
-- make sure the key lists don't contain: backspace, or duplicates -- make sure the key lists don't contain: backspace, our cancel key, or duplicates
sanitise :: [KeySym] -> [KeySym] sanitise :: [KeySym] -> [KeySym]
sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf]) sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf])
sanitiseKeys :: ChordKeys -> ChordKeys sanitiseKeys :: ChordKeys -> ChordKeys
@@ -336,7 +342,7 @@ selectWindow conf =
appendChords :: Int -> [KeySym] -> [OverlayWindow] -> [Overlay] appendChords :: Int -> [KeySym] -> [OverlayWindow] -> [Overlay]
appendChords _ [] _ = [] appendChords _ [] _ = []
appendChords maxUserSelectedLen ks overlayWins = appendChords maxUserSelectedLen ks overlayWins =
zipWith (\ow c -> Overlay { overlayWin=ow, chord=c }) overlayWins chords zipWith Overlay overlayWins chords
where where
chords = replicateM chordLen ks chords = replicateM chordLen ks
-- the minimum necessary chord length to assign a unique chord to each visible window -- the minimum necessary chord length to assign a unique chord to each visible window
@@ -365,6 +371,7 @@ handleKeyboard dpy drawFn cancel selected deselected = do
| isNextOverlayKey s -> handleNextOverlayKey s | isNextOverlayKey s -> handleNextOverlayKey s
| otherwise -> handleKeyboard dpy drawFn cancel selected deselected | otherwise -> handleKeyboard dpy drawFn cancel selected deselected
| ev_event_type ev == buttonPress -> do | ev_event_type ev == buttonPress -> do
-- See XMonad.Prompt Note [Allow ButtonEvents]
io $ allowEvents dpy replayPointer currentTime io $ allowEvents dpy replayPointer currentTime
handleKeyboard dpy drawFn cancel selected deselected handleKeyboard dpy drawFn cancel selected deselected
| otherwise -> handleKeyboard dpy drawFn cancel selected deselected | otherwise -> handleKeyboard dpy drawFn cancel selected deselected
@@ -374,12 +381,12 @@ handleKeyboard dpy drawFn cancel selected deselected = do
case x of case x of
Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected
_ -> return x _ -> return x
isNextOverlayKey keySym = isJust (L.find ((== keySym) . head .chord) selected) isNextOverlayKey keySym = isJust (L.find ((== Just keySym) . listToMaybe .chord) selected)
handleNextOverlayKey keySym = handleNextOverlayKey keySym =
case fg of case fg of
[x] -> return $ Selected x [x] -> return $ Selected x
_ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace _ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace
where where
(fg, bg) = L.partition ((== keySym) . head . chord) selected (fg, bg) = L.partition ((== Just keySym) . listToMaybe . chord) selected
trim = map (\o -> o { chord = tail $ chord o }) trim = map (\o -> o { chord = tail $ chord o })
clear = map (\o -> o { chord = [] }) clear = map (\o -> o { chord = [] })