[xmonad] contrib: fixing raiseNext stuck between 2 workspaces
Loïc
loic at inzenet.org
Sun Nov 13 13:24:28 UTC 2016
Dear all,
I'm a big fan of raiseNext(Maybe) action from xmonad-contrib.
However, there is a quite annoying bug, reported some years ago still active:
raiseNext cycles only between 2 workspaces, making impossible to cycle through
the entire list of windows (for a full description, not by me, see
https://code.google.com/archive/p/xmonad/issues/284 )
The reason is that raiseNext calls allWindows from xmonad StackSet, which
relies on a list of workspaces built as follows: the current workspace is put
first, followed by visible then hidden workspaces.
Thus the ordering of workspaces is not absolute, which is why raiseNext will
cycle only between the current and another workspace.
I found the following fix:
- create a allWindowsSorted function in Xmonad.StackSet which relies on a list
of workspaces sorted by their tags
- call W.allWindowsSorted instead of W.allWindows in raiseNext.
The patch is given below for 0.12.
Let me know if it is an appropriate way to fix the bug. If so, I can create
the
pull requests for xmonad and xmonad-contrib that apply on current master.
Otherwise, let me know what solution you would prefer.
It would be nice that 0.13 contains a fix.
Thanks for your feedback,
Loïc
diff -ur xmonad-0.12/src/XMonad/StackSet.hs xmonad-0.12.new/src/XMonad/
StackSet.hs
--- xmonad-0.12/src/XMonad/StackSet.hs 2015-12-21 20:12:39.000000000 +0100
+++ xmonad-0.12.new/src/XMonad/StackSet.hs 2016-11-10 00:00:06.277840982
+0100
@@ -31,7 +31,7 @@
-- * Xinerama operations
-- $xinerama
lookupWorkspace,
- screens, workspaces, allWindows, currentTag,
+ screens, workspaces, allWindows, allWindowsSorted, currentTag,
-- * Operations on the current stack
-- $stackOperations
peek, index, integrate, integrate', differentiate,
@@ -53,7 +53,7 @@
import Prelude hiding (filter)
import Data.Maybe (listToMaybe,isJust,fromMaybe)
-import qualified Data.List as L (deleteBy,find,splitAt,filter,nub)
+import qualified Data.List as L (deleteBy,find,splitAt,filter,nub,sortBy)
import Data.List ( (\\) )
import qualified Data.Map as M (Map,insert,delete,empty)
@@ -385,6 +385,15 @@
allWindows :: Eq a => StackSet i l a s sd -> [a]
allWindows = L.nub . concatMap (integrate' . stack) . workspaces
+
+workspacesSorted :: Ord i => StackSet i l a s sd -> [Workspace i l a]
+workspacesSorted s = L.sortBy (\u t -> tag u `compare` tag t) $
+ workspaces s
+
+-- | Get a list of all windows in the 'StackSet' with an absolute ordering of
workspaces
+allWindowsSorted :: Ord i => Eq a => StackSet i l a s sd -> [a]
+allWindowsSorted = L.nub . concatMap (integrate' . stack) . workspacesSorted
+
-- | Get the tag of the currently focused workspace.
currentTag :: StackSet i l a s sd -> i
currentTag = tag . workspace . current
diff -ur xmonad-contrib-0.12/XMonad/Actions/WindowGo.hs xmonad-
contrib-0.12.new/XMonad/Actions/WindowGo.hs
--- xmonad-contrib-0.12/XMonad/Actions/WindowGo.hs 2015-12-21
20:15:08.000000000 +0100
+++ xmonad-contrib-0.12.new/XMonad/Actions/WindowGo.hs 2016-11-10
00:05:33.422854352 +0100
@@ -43,7 +43,7 @@
import XMonad.ManageHook
import XMonad.Operations (windows)
import XMonad.Prompt.Shell (getBrowser, getEditor)
-import qualified XMonad.StackSet as W (allWindows, peek, swapMaster,
focusWindow)
+import qualified XMonad.StackSet as W (allWindowsSorted, peek, swapMaster,
focusWindow)
import XMonad.Util.Run (safeSpawnProg)
{- $usage
@@ -70,7 +70,7 @@
-- second parameter.
ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows qry f el = withWindowSet $ \wins -> do
- matches <- filterM (runQuery qry) $ W.allWindows wins
+ matches <- filterM (runQuery qry) $ W.allWindowsSorted wins
case matches of
[] -> el
ws -> f ws
More information about the xmonad
mailing list