Use reverseS instead of self-defined functions

This commit is contained in:
slotThe 2021-03-29 17:50:03 +02:00
parent 02d0b79289
commit 6ece010c01
4 changed files with 8 additions and 13 deletions

View File

@ -29,6 +29,7 @@ import Data.List (partition, sortOn, (\\))
import qualified Data.Map as M import qualified Data.Map as M
import XMonad (Window, WindowSpace, Rectangle, 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)
import XMonad.Util.Stack (reverseS)
{- $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@:
@ -101,7 +102,7 @@ surfaceNext = do
surfacePrev :: X () surfacePrev :: X ()
surfacePrev = do surfacePrev = do
ring <- surfaceRing ring <- surfaceRing
windows . modify' $ reverseStack . rotateSome (`elem` ring) . reverseStack windows . modify' $ reverseS . rotateSome (`elem` ring) . reverseS
-- | -- |
-- Return a list containing the current focus plus any unshown windows. Note -- Return a list containing the current focus plus any unshown windows. Note
@ -158,6 +159,3 @@ rotateSome p (Stack t ls rs) =
rotate :: [a] -> [a] rotate :: [a] -> [a]
rotate = uncurry (flip (++)) . splitAt 1 rotate = uncurry (flip (++)) . splitAt 1
reverseStack :: Stack a -> Stack a
reverseStack (Stack t ls rs) = Stack t rs ls

View File

@ -24,6 +24,7 @@ module XMonad.Actions.Sift (
) where ) where
import XMonad.StackSet (Stack (Stack), StackSet, modify') import XMonad.StackSet (Stack (Stack), StackSet, modify')
import XMonad.Util.Stack (reverseS)
-- $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@:
@ -44,7 +45,7 @@ import XMonad.StackSet (Stack (Stack), StackSet, modify')
-- --
siftUp, siftDown :: StackSet i l a s sd -> StackSet i l a s sd siftUp, siftDown :: StackSet i l a s sd -> StackSet i l a s sd
siftUp = modify' siftUp' siftUp = modify' siftUp'
siftDown = modify' (reverseStack . siftUp' . reverseStack) siftDown = modify' (reverseS . siftUp' . reverseS)
siftUp' :: Stack a -> Stack a siftUp' :: Stack a -> Stack a
siftUp' (Stack t (l:ls) rs) = Stack t ls (l:rs) siftUp' (Stack t (l:ls) rs) = Stack t ls (l:rs)
@ -52,6 +53,3 @@ siftUp' (Stack t [] rs) =
case reverse rs of case reverse rs of
(x:xs) -> Stack t (xs ++ [x]) [] (x:xs) -> Stack t (xs ++ [x]) []
[] -> Stack t [] [] [] -> Stack t [] []
reverseStack :: Stack a -> Stack a
reverseStack (Stack t ls rs) = Stack t rs ls

View File

@ -48,6 +48,7 @@ import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
LayoutModifier(handleMess, redoLayout)) LayoutModifier(handleMess, redoLayout))
import XMonad(Typeable, Message, WorkspaceId, X, XState(windowset), import XMonad(Typeable, Message, WorkspaceId, X, XState(windowset),
fromMessage, sendMessage, windows, gets) fromMessage, sendMessage, windows, gets)
import XMonad.Util.Stack (reverseS)
import Control.Applicative (liftA2) import Control.Applicative (liftA2)
import Control.Monad((<=<), guard, when) import Control.Monad((<=<), guard, when)
import Data.Foldable(toList) import Data.Foldable(toList)
@ -151,8 +152,7 @@ noWrapUp x@(W.Stack _ [] _ ) = x
-- | non-wrapping version of 'W.focusDown'' -- | non-wrapping version of 'W.focusDown''
noWrapDown :: W.Stack t -> W.Stack t noWrapDown :: W.Stack t -> W.Stack t
noWrapDown = reverseStack . noWrapUp . reverseStack noWrapDown = reverseS . noWrapUp . reverseS
where reverseStack (W.Stack t ls rs) = W.Stack t rs ls
focusDepth :: Cursors t -> Int focusDepth :: Cursors t -> Int
focusDepth (Cons x) = 1 + focusDepth (W.focus x) focusDepth (Cons x) = 1 + focusDepth (W.focus x)

View File

@ -143,13 +143,13 @@ instance LayoutModifier BoringWindows Window where
do windows $ W.modify' skipBoringSwapUp do windows $ W.modify' skipBoringSwapUp
return Nothing return Nothing
| Just SwapDown <- fromMessage m = | Just SwapDown <- fromMessage m =
do windows $ W.modify' (reverseStack . skipBoringSwapUp . reverseStack) do windows $ W.modify' (reverseS . skipBoringSwapUp . reverseS)
return Nothing return Nothing
| Just SiftUp <- fromMessage m = | Just SiftUp <- fromMessage m =
do windows $ W.modify' (siftUpSkipping bs) do windows $ W.modify' (siftUpSkipping bs)
return Nothing return Nothing
| Just SiftDown <- fromMessage m = | Just SiftDown <- fromMessage m =
do windows $ W.modify' (reverseStack . siftUpSkipping bs . reverseStack) do windows $ W.modify' (reverseS . siftUpSkipping bs . reverseS)
return Nothing return Nothing
where skipBoring = skipBoring' ((`notElem` bs) . W.focus) where skipBoring = skipBoring' ((`notElem` bs) . W.focus)
skipBoringSwapUp = skipBoring' skipBoringSwapUp = skipBoring'
@ -162,7 +162,6 @@ instance LayoutModifier BoringWindows Window where
$ iterate f st $ iterate f st
bs = concat $ cbs:maybeToList lbs ++ M.elems nbs bs = concat $ cbs:maybeToList lbs ++ M.elems nbs
rjl = return . Just . Left rjl = return . Just . Left
reverseStack (W.Stack t ls rs) = W.Stack t rs ls
handleMessOrMaybeModifyIt _ _ = return Nothing handleMessOrMaybeModifyIt _ _ = return Nothing
-- | Variant of 'focusMaster' that works on a -- | Variant of 'focusMaster' that works on a