improve RotateSome documentation and readability

Add an example and more comments to the documentation, and make some
small code tweaks (more type signatures and a couple variable renames)
to aid readability.
This commit is contained in:
ivanbrennan 2020-09-23 16:55:14 -04:00
parent 8fe0eabaf8
commit c5ff88b87b
No known key found for this signature in database
GPG Key ID: 79C3C47DC652EA54

View File

@ -17,6 +17,8 @@
module XMonad.Actions.RotateSome ( module XMonad.Actions.RotateSome (
-- * Usage -- * Usage
-- $usage -- $usage
-- * Example
-- $example
surfaceNext, surfaceNext,
surfacePrev, surfacePrev,
rotateSome, rotateSome,
@ -25,19 +27,67 @@ module XMonad.Actions.RotateSome (
import Control.Arrow ((***)) import Control.Arrow ((***))
import Data.List (partition, sortOn, (\\)) import Data.List (partition, sortOn, (\\))
import qualified Data.Map as M import qualified Data.Map as M
import XMonad (Window, X, runLayout, screenRect, windows, withWindowSet) import XMonad (Window, WindowSpace, Rectangle, X, runLayout, screenRect, windows, withWindowSet)
import XMonad.StackSet (Screen (Screen), Stack (Stack), current, floating, modify', stack) import XMonad.StackSet (Screen (Screen), Stack (Stack), current, floating, modify', stack)
-- $usage {- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.RotateSome > import XMonad.Actions.RotateSome
--
-- and add keybindings such as the following: and add keybindings such as the following:
--
-- > , ((modMask .|. controlMask, xK_n), surfaceNext) > , ((modMask .|. controlMask, xK_n), surfaceNext)
-- > , ((modMask .|. controlMask, xK_p), surfacePrev) > , ((modMask .|. controlMask, xK_p), surfacePrev)
--
-}
{- $example
#Example#
Consider a workspace whose stack contains five windows A B C D E but whose
layout limits how many will actually be shown, showing only the first plus
two additional windows, starting with the third:
>
> C
> A
> D
>
>
> A B C D E
> _ ____
If C has focus and we'd like to replace it with one of the unshown windows,
'surfaceNext' will move the next unshown window, E, into the focused position:
>
> *C* *E*
> A surfaceNext -> A
> D D
>
>
> A B *C* D E A C *E* D B
> _ ____ _ ____
This repositioned windows B C E by treating them as a sequence that can be
rotated through the focused stack position. Windows A and D remain anchored
to their original (visible) positions.
A second call to 'surfaceNext' moves B into focus:
>
> *E* *B*
> A surfaceNext -> A
> D D
>
>
> A C *E* D B A E *B* D C
> _ ____ _ ____
A third call would complete the cycle, bringing C back into focus.
-}
-- | -- |
-- Treating the focused window and any unshown windows as a ring that can be -- Treating the focused window and any unshown windows as a ring that can be
@ -53,15 +103,23 @@ surfacePrev = do
ring <- surfaceRing ring <- surfaceRing
windows . modify' $ reverseStack . rotateSome (`elem` ring) . reverseStack windows . modify' $ reverseStack . rotateSome (`elem` ring) . reverseStack
-- |
-- Return a list containing the current focus plus any unshown windows. Note
-- that windows are shown if 'runLayout' provides them with a rectangle or if
-- they are floating.
surfaceRing :: X [Window] surfaceRing :: X [Window]
surfaceRing = withWindowSet $ \wset -> do surfaceRing = withWindowSet $ \wset -> do
let Screen wsp _ sd = current wset let Screen wsp _ sd = current wset
case stack wsp >>= filter' (`M.notMember` floating wset) of case stack wsp >>= filter' (`M.notMember` floating wset) of
Nothing -> pure [] Nothing -> pure []
Just st -> go st . fst <$> runLayout wsp {stack = Just st} (screenRect sd) Just st -> go st <$> layoutWindows wsp {stack = Just st} (screenRect sd)
where where
go (Stack t ls rs) recs = t : ((ls ++ rs) \\ map fst recs) go :: Stack Window -> [Window] -> [Window]
go (Stack t ls rs) shown = t : ((ls ++ rs) \\ shown)
layoutWindows :: WindowSpace -> Rectangle -> X [Window]
layoutWindows wsp rect = map fst . fst <$> runLayout wsp rect
-- | Like "XMonad.StackSet.filter" but won't move focus. -- | Like "XMonad.StackSet.filter" but won't move focus.
filter' :: (a -> Bool) -> Stack a -> Maybe (Stack a) filter' :: (a -> Bool) -> Stack a -> Maybe (Stack a)
@ -76,19 +134,25 @@ filter' p (Stack f ls rs)
rotateSome :: (a -> Bool) -> Stack a -> Stack a rotateSome :: (a -> Bool) -> Stack a -> Stack a
rotateSome p (Stack t ls rs) = rotateSome p (Stack t ls rs) =
let let
(xs, anchors) = -- Flatten the stack, index each element relative to the focused position,
-- then partition into movable and anchored elements.
(movables, anchors) =
partition (p . snd) $ partition (p . snd) $
zip zip
[negate (length ls)..] [negate (length ls)..]
(reverse ls ++ t : rs) (reverse ls ++ t : rs)
-- Pair each movable element with the index of its next movable neighbor.
-- Append anchored elements, along with their unchanged indices, and sort
-- by index. Separate lefts (negative indices) from the rest, and grab the
-- new focus from the head of the remaining elements.
(ls', t':rs') = (ls', t':rs') =
(map snd *** map snd) (map snd *** map snd)
. span ((< 0) . fst) . span ((< 0) . fst)
. sortOn fst . sortOn fst
. (++) anchors . (++) anchors
. map (fst *** snd) . map (fst *** snd)
$ zip xs (rotate xs) $ zip movables (rotate movables)
in in
Stack t' (reverse ls') rs' Stack t' (reverse ls') rs'