mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-31 20:21:52 -07:00
Change semantics of 'promote'.
Previously 'promote' would move the currently focused window into the master position in tiled mode. This was *almost* a cycle of the windows, but not quite (depending on where the focus was, it was in fact a cycle). Now we do the obvious generalisation, and just cycle the current window stack. Simpler to understand, simpler to reason about.
This commit is contained in:
@@ -123,7 +123,7 @@ keys = M.fromList $
|
||||
, ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess)
|
||||
, ((modMask .|. shiftMask .|. controlMask, xK_q ), io restart)
|
||||
|
||||
-- Move focused window into master position in tiling mode.
|
||||
-- Cycle the current tiling order
|
||||
, ((modMask, xK_Return), promote)
|
||||
|
||||
] ++
|
||||
|
@@ -34,7 +34,7 @@ refresh = do
|
||||
mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $
|
||||
case layoutType fl of
|
||||
Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws
|
||||
Tall -> tile (tileFraction fl) sc $ W.index n ws
|
||||
Tall -> tile (tileFraction fl) sc $ W.index n ws
|
||||
Wide -> vtile (tileFraction fl) sc $ W.index n ws
|
||||
whenJust (W.peekStack n ws) (io . raiseWindow d)
|
||||
whenJust (W.peek ws) setFocus
|
||||
@@ -192,13 +192,9 @@ setBorder w p = withDisplay $ \d -> io $ setWindowBorder d w p
|
||||
raise :: Ordering -> X ()
|
||||
raise = windows . W.rotate
|
||||
|
||||
-- | promote. Make the focused window the master window in its
|
||||
-- workspace
|
||||
--
|
||||
-- TODO: generic cycling clockwise and anticlockwise
|
||||
--
|
||||
-- | promote. Cycle the current tiling order clockwise.
|
||||
promote :: X ()
|
||||
promote = windows $ \w -> maybe w (\k -> W.promote k w) (W.peek w)
|
||||
promote = windows W.promote
|
||||
|
||||
-- | Kill the currently focused client
|
||||
kill :: X ()
|
||||
|
21
StackSet.hs
21
StackSet.hs
@@ -162,6 +162,8 @@ visibleWorkspaces = M.keys . ws2screen
|
||||
|
||||
--
|
||||
-- | /O(log n)/. rotate. cycle the current window list up or down.
|
||||
-- Has the effect of rotating focus. In fullscreen mode this will cause
|
||||
-- a new window to be visible.
|
||||
--
|
||||
-- rotate EQ --> [5,6,7,8,1,2,3,4]
|
||||
-- rotate GT --> [6,7,8,1,2,3,4,5]
|
||||
@@ -177,7 +179,7 @@ rotate o w = maybe w id $ do
|
||||
EQ -> Nothing
|
||||
GT -> elemAfter f s
|
||||
LT -> elemAfter f (reverse s)
|
||||
return (w { focus = M.insert (current w) ea (focus w) })
|
||||
return $ w { focus = M.insert (current w) ea (focus w) }
|
||||
|
||||
-- | /O(log n)/. shift. move the client on top of the current stack to
|
||||
-- the top of stack 'n'. If the stack to move to is not valid, and
|
||||
@@ -217,11 +219,18 @@ raiseFocus k w = case M.lookup k (cache w) of
|
||||
Nothing -> w
|
||||
Just i -> (view i w) { focus = M.insert i k (focus w) }
|
||||
|
||||
-- | Move a window to the top of its workspace.
|
||||
promote :: Ord a => a -> StackSet a -> StackSet a
|
||||
promote k w = case M.lookup k (cache w) of
|
||||
Nothing -> w
|
||||
Just i -> w { stacks = M.adjust (\ks -> k : filter (/= k) ks) i (stacks w) }
|
||||
-- | Cycle the current stack ordering. In tiled mode has the effect of
|
||||
-- moving a new window into the master position, without changing focus.
|
||||
promote :: StackSet a -> StackSet a
|
||||
promote w = w { stacks = M.adjust next (current w) (stacks w) }
|
||||
where next [] = []
|
||||
next xs = last xs : init xs
|
||||
|
||||
--
|
||||
-- case M.lookup k (cache w) of
|
||||
-- Nothing -> w
|
||||
-- Just i -> w { stacks = M.adjust (\ks -> k : filter (/= k) ks) i (stacks w) }
|
||||
--
|
||||
|
||||
-- |
|
||||
elemAfter :: Eq a => a -> [a] -> Maybe a
|
||||
|
Reference in New Issue
Block a user