X.A.CycleRecentWS: Cycle workspaces, not windowsets

The way that workspace cycling is implemented right now—by generating
new windowsets where the things we want happen to be true and then
replacing the old windowsets—is not safe, as workspaces and layouts may
carry state with them.  That state will get lost in translation when
windowsets are simply replaced.

As an example, a conflict occurs when using `X.L.ShowWName.showWName` in
one's layoutHook.  When cycling through workspaces via, e.g.,
`cycleRecentWS` the flashed workspace tag will not disappear, as the
necessary state to control this isn't present in the new windowset.

Instead, what we want to do is to keep the "current" windowset alive and
actually switch to the requested workspaces.  This mostly works without
much trouble, the only hard part is maintaining the invariant that
previewed workspaces don't count towards the history of recently-viewed
workspaces.  This is done by remembering the tag-order of the original
windowset and then restoring that at the end.

This is a breaking change, insofar as it changes the type signatures of
the exported functions `recentWS`, `cycleWindowSets`, and
`toggleWindowSets` to return a list of `WorkspaceId`s instead of a list
of `WindowSet`s.

Fixes: https://github.com/xmonad/xmonad-contrib/issues/504
This commit is contained in:
slotThe 2021-05-11 15:36:20 +02:00
parent f4673d611b
commit f0809e5d1d

View File

@ -1,3 +1,4 @@
{-# LANGUAGE MultiWayIf #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.CycleRecentWS
@ -30,6 +31,10 @@ module XMonad.Actions.CycleRecentWS (
import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter)
import Control.Arrow ((&&&))
import Data.List (find)
import Data.Maybe (fromJust)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
--
@ -76,56 +81,97 @@ toggleRecentNonEmptyWS :: X ()
toggleRecentNonEmptyWS = toggleWindowSets $ recentWS (not . null . stack)
-- | Given a predicate p and the current WindowSet w, create a list of recent WindowSets,
-- most recent first, where the focused workspace satisfies p.
-- | Given a predicate @p@ and the current 'WindowSet' @w@, create a
-- list of workspaces to choose from. They are ordered by recency and
-- have to satisfy @p@.
recentWS :: (WindowSpace -> Bool) -- ^ A workspace predicate.
-> WindowSet -- ^ The current WindowSet
-> [WindowSet]
recentWS p w = map (`view` w) recentTags
where recentTags = map tag
-> [WorkspaceId]
recentWS p w = map tag
$ filter p
$ map workspace (visible w)
++ hidden w
++ [workspace (current w)]
cycref :: [a] -> Int -> a
cycref l i = l !! (i `mod` length l)
-- | Cycle through a finite list of WindowSets with repeated presses of a key, while
-- | Cycle through a finite list of workspaces with repeated presses of a key, while
-- a modifier key is held down. For best effects use the same modkey+key combination
-- as the one used to invoke this action.
cycleWindowSets :: (WindowSet -> [WindowSet]) -- ^ A function used to create a list of WindowSets to choose from
cycleWindowSets :: (WindowSet -> [WorkspaceId]) -- ^ A function used to create a list of workspaces to choose from
-> [KeySym] -- ^ A list of modifier keys used when invoking this action.
-- As soon as one of them is released, the final WindowSet is chosen and the action exits.
-> KeySym -- ^ Key used to preview next WindowSet from the list of generated options
-> KeySym -- ^ Key used to preview previous WindowSet from the list of generated options.
-- As soon as one of them is released, the final workspace is chosen and the action exits.
-> KeySym -- ^ Key used to preview next workspace from the list of generated options
-> KeySym -- ^ Key used to preview previous workspace from the list of generated options.
-- If it's the same as nextOption key, it is effectively ignored.
-> X ()
cycleWindowSets genOptions mods keyNext keyPrev = do
options <- gets $ genOptions . windowset
origWSet <- gets windowset
let options = genOptions origWSet
XConf {theRoot = root, display = d} <- ask
let event = allocaXEvent $ \p -> do
maskEvent d (keyPressMask .|. keyReleaseMask) p
KeyEvent {ev_event_type = t, ev_keycode = c} <- getEvent p
s <- keycodeToKeysym d c 0
return (t, s)
let setOption n = do windows $ const $ options `cycref` n
let setOption n = do
let nextWs = options `cycref` n
syncW ws = windows $ view ws . restoreOrder origWSet
(t, s) <- io event
case () of
() | t == keyPress && s == keyNext -> setOption (n+1)
| t == keyPress && s == keyPrev -> setOption (n-1)
| t == keyRelease && s `elem` mods -> return ()
if | t == keyPress && s == keyNext -> syncW nextWs >> setOption (n + 1)
| t == keyPress && s == keyPrev -> syncW nextWs >> setOption (n - 1)
| t == keyRelease && s `elem` mods ->
syncW =<< gets (tag . workspace . current . windowset)
| otherwise -> setOption n
io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime
setOption 0
windows $ view (options `cycref` 0) -- view the first ws
setOption 1
io $ ungrabKeyboard d currentTime
where
cycref :: [a] -> Int -> a
cycref l i = l !! (i `mod` length l)
-- | Given an old and a new 'WindowSet', which is __exactly__ one
-- 'view' away from the old one, restore the workspace order of the
-- former inside of the latter. This respects any new state that the
-- new 'WindowSet' may have accumulated.
restoreOrder :: WindowSet -> WindowSet -> WindowSet
restoreOrder origW w
| -- The focused screen changed; the old focus is on a visible screen
newFocT `elem` visT =
w { current = (current origW){ workspace = findFoc (workspace <$> visible w) }
, visible = zipWith (\v ws -> v{ workspace = ws }) vis (updateNewFoc visW)
}
| -- The focused screen didn't change; the old focus is hidden
newFocT `elem` hidT =
w { current = (current origW){ workspace = findFoc (hidden w) }
, hidden = updateNewFoc hid
}
| otherwise = w
where
-- Foci, old and new
focT = tag . workspace . current $ origW
(newFoc, newFocT) = id &&& tag $ workspace (current w)
-- | Switch to the first of a finite list of WindowSets.
toggleWindowSets :: (WindowSet -> [WindowSet]) -> X ()
-- Workspaces in the _original_ windowset
(hid, hidT) = id &&& map tag $ hidden origW
(vis, (visW, visT)) = id &&& map workspace &&& map (tag . workspace)
$ visible origW
-- | Given a list of new workspaces that contain the old focus,
-- return that workspace.
findFoc :: [WindowSpace] -> WindowSpace
findFoc ws = fromJust $ find ((== focT) . tag) ws
-- | Given a list of old workspaces that contain the new focus,
-- update the state of the focus.
updateNewFoc :: [WindowSpace] -> [WindowSpace]
updateNewFoc ws = before ++ newFoc : after
where (before, after) = drop 1 <$> break ((== newFocT) . tag) ws
-- | Given some function that generates a list of workspaces from a
-- given 'WindowSet', switch to the first generated workspace.
toggleWindowSets :: (WindowSet -> [WorkspaceId]) -> X ()
toggleWindowSets genOptions = do
options <- gets $ genOptions . windowset
case options of
[] -> return ()
o:_ -> windows (const o)
o:_ -> windows (view o)