X.U.Stack: Add zipperFocusedAtFirstOf

This commit is contained in:
Tony Zorman 2023-09-19 09:13:15 +02:00
parent 52a40f376c
commit 8ee129483a
6 changed files with 47 additions and 61 deletions

View File

@ -265,6 +265,11 @@
- Added `passOTPTypePrompt` to type out one-time-passwords via
`xdotool`.
* `XMonad.Util.Stack`
- Added `zipperFocusedAtFirstOf` to differentiate two lists into a
zipper.
### Other changes
## 0.17.1 (September 3, 2022)

View File

@ -1,5 +1,8 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses,
UndecidableInstances, PatternGuards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE UndecidableInstances #-}
-----------------------------------------------------------------------------
-- |
@ -24,10 +27,10 @@ module XMonad.Layout.Combo (
) where
import XMonad hiding (focus)
import XMonad.Layout.WindowNavigation (MoveWindowToWindow (..))
import XMonad.Prelude (delete, fromMaybe, intersect, isJust, (\\))
import XMonad.StackSet ( integrate', Workspace (..), Stack(..) )
import XMonad.Layout.WindowNavigation ( MoveWindowToWindow(..) )
import qualified XMonad.StackSet as W ( differentiate )
import XMonad.StackSet (Stack (..), Workspace (..), integrate')
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -94,8 +97,8 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a,
[] -> init x
_ -> x
superstack = Stack { focus=(), up=[], down=[()] }
s1 = differentiate f' (origws \\ w2')
s2 = differentiate f' w2'
s1 = zipperFocusedAtFirstOf f' (origws \\ w2')
s2 = zipperFocusedAtFirstOf f' w2'
f' = case s of (Just s') -> focus s':delete (focus s') f
Nothing -> f
([((),r1),((),r2)], msuper') <- runLayout (Workspace "" super (Just superstack)) rinput
@ -128,14 +131,6 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a,
description (C2 _ _ super l1 l2) = "combining "++ description l1 ++" and "++
description l2 ++" with "++ description super
differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q)
differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z
, up = reverse $ takeWhile (/=z) xs
, down = drop 1 $ dropWhile (/=z) xs }
| otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs
broadcastPrivate :: LayoutClass l b => SomeMessage -> [l b] -> X (Maybe [l b])
broadcastPrivate a ol = do nml <- mapM f ol
if any isJust nml

View File

@ -25,12 +25,13 @@ module XMonad.Layout.ComboP (
Property(..)
) where
import XMonad.Prelude
import XMonad hiding (focus)
import XMonad.StackSet ( Workspace (..), Stack(..) )
import XMonad.Layout.WindowNavigation
import XMonad.Util.WindowProperties
import XMonad.Prelude
import XMonad.StackSet ( Workspace (..), Stack(..) )
import qualified XMonad.StackSet as W
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
import XMonad.Util.WindowProperties
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -99,10 +100,10 @@ instance (LayoutClass l (), LayoutClass l1 Window, LayoutClass l2 Window) =>
f' = focus s:delete (focus s) f -- list of focused windows, contains 2 elements at most
in do
matching <- hasProperty prop `filterM` new -- new windows matching predecate
let w1' = w1c ++ matching -- updated first pane windows
w2' = w2c ++ (new \\ matching) -- updated second pane windows
s1 = differentiate f' w1' -- first pane stack
s2 = differentiate f' w2' -- second pane stack
let w1' = w1c ++ matching -- updated first pane windows
w2' = w2c ++ (new \\ matching) -- updated second pane windows
s1 = zipperFocusedAtFirstOf f' w1' -- first pane stack
s2 = zipperFocusedAtFirstOf f' w2' -- second pane stack
([((),r1),((),r2)], msuper') <- runLayout (Workspace "" super superstack) rinput
(wrs1, ml1') <- runLayout (Workspace "" l1 s1) r1
(wrs2, ml2') <- runLayout (Workspace "" l2 s2) r2
@ -177,15 +178,4 @@ forwardIfFocused l w m = do
then handleMessage l m
else return Nothing
-- code from CombineTwo
-- given two sets of zs and xs takes the first z from zs that also belongs to xs
-- and turns xs into a stack with z being current element. Acts as
-- StackSet.differentiate if zs and xs don't intersect
differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q)
differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z
, up = reverse $ takeWhile (/=z) xs
, down = tail $ dropWhile (/=z) xs }
| otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs
-- vim:ts=4:shiftwidth=4:softtabstop=4:expandtab:foldlevel=20:

View File

@ -57,9 +57,11 @@ module XMonad.Layout.LayoutBuilder (
LayoutN,
) where
import Data.Maybe (maybeToList)
import XMonad
import XMonad.Prelude (foldM, (<|>), isJust, fromMaybe, isNothing, listToMaybe)
import qualified XMonad.StackSet as W
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
import XMonad.Util.WindowProperties
--------------------------------------------------------------------------------
@ -452,11 +454,4 @@ calcArea (SubBox xpos ypos width height) rect =
--------------------------------------------------------------------------------
differentiate' :: Eq q => Maybe q -> [q] -> Maybe (W.Stack q)
differentiate' _ [] = Nothing
differentiate' Nothing w = W.differentiate w
differentiate' (Just f) w
| f `elem` w = Just W.Stack { W.focus = f
, W.up = reverse $ takeWhile (/=f) w
, W.down = tail $ dropWhile (/=f) w
}
| otherwise = W.differentiate w
differentiate' = zipperFocusedAtFirstOf . maybeToList

View File

@ -42,12 +42,13 @@ module XMonad.Layout.TallMastersCombo (
) where
import XMonad hiding (focus, (|||))
import XMonad.Prelude (delete, find, foldM, fromMaybe, isJust)
import XMonad.StackSet (Workspace(..),integrate',Stack(..))
import qualified XMonad.StackSet as W
import qualified XMonad.Layout as LL
import XMonad.Layout.Simplest (Simplest(..))
import XMonad.Layout.Decoration
import XMonad.Layout.Simplest (Simplest (..))
import XMonad.Prelude (delete, find, foldM, fromMaybe, isJust)
import XMonad.StackSet (Stack (..), Workspace (..), integrate')
import qualified XMonad.StackSet as W
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
---------------------------------------------------------------------------------
-- $usage
@ -302,19 +303,6 @@ instance (GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombine
mlayout2 <- handleMessage layout2 m
return $ mergeSubLayouts mlayout1 mlayout2 i False
-- code from CombineTwo
-- given two sets of zs and xs takes the first z from zs that also belongs to xs
-- and turns xs into a stack with z being current element. Acts as
-- StackSet.differentiate if zs and xs don't intersect
differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q)
differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z
, up = reverse $ takeWhile (/=z) xs
, down = tail $ dropWhile (/=z) xs }
| otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs
-- | Swap a given window with the focused window.
swapWindow :: (Eq a) => a -> Stack a -> Stack a
swapWindow w (Stack foc upLst downLst)
@ -388,9 +376,9 @@ splitStack f nmaster frac s =
Nothing -> f
snum = length slst
(slst1, slst2) = splitAt nmaster slst
s0 = differentiate f' slst
s1' = differentiate f' slst1
s2' = differentiate f' slst2
s0 = zipperFocusedAtFirstOf f' slst
s1' = zipperFocusedAtFirstOf f' slst1
s2' = zipperFocusedAtFirstOf f' slst2
(s1,s2,frac') | nmaster == 0 = (Nothing,s0,0)
| nmaster >= snum = (s0,Nothing,1)
| otherwise = (s1',s2',frac)

View File

@ -27,6 +27,7 @@ module XMonad.Util.Stack ( -- * Usage
, toIndex
, fromTags
, toTags
, zipperFocusedAtFirstOf
-- * 'Zipper' manipulation functions
-- ** Insertion, movement
@ -123,6 +124,18 @@ toTags Nothing = []
toTags (Just s) = map Left (reverse . W.up $ s) ++ [Right . W.focus $ s]
++ map Left (W.down s)
-- | @differentiate zs xs@ takes the first @z@ from @z2 that also belongs to
-- @xs@ and turns @xs@ into a stack with @z@ being the current element. Acts
-- as 'XMonad.StackSet.differentiate' if @zs@ and @xs@ don't intersect.
zipperFocusedAtFirstOf :: Eq q => [q] -> [q] -> Zipper q
zipperFocusedAtFirstOf [] xs = W.differentiate xs
zipperFocusedAtFirstOf (z : zs) xs
| z `elem` xs = Just $
W.Stack { W.focus = z
, W.up = reverse $ takeWhile (/= z) xs
, W.down = drop 1 $ dropWhile (/= z) xs
}
| otherwise = zipperFocusedAtFirstOf zs xs
-- * Zipper functions