
[ Apologies if this is a duplicate -- I haven't seen it show up on the list, so I'm resending from the address that I subscribed with. ] Hi all. I just started using xmonad, and there's a layout I want to have but can't quite figure out how to get. I'm sure it's just a matter of gluing the right pieces from the contrib library together, but I haven't gotten it right yet. I want the workspace to be divided vertically into two areas. Each area should show just one window at a time. Pressing Alt-Tab (or something) should cycle through, in the currently focused half of the screen, all windows except the one that's visible in the other area. The idea being that visible but non-focused windows should stay visible and non-focused. For example, assume the workspace has five windows, A through E, with C and E currently visible. Alt-Tabbing when the focus is on the left half of the workspace should cycle through A, B, C, and D; if the right half is focused, we should cycle through A, B, D, and E. XMonad.Actions.CycleWS lets me do exactly this with workspaces and two Xinerama screens, by binding (moveTo Next HiddenNonEmptyWS) to a key. -- Karl Hasselström, kha@treskal.com www.treskal.com/kalle

2009/1/20 Karl Hasselström
[ Apologies if this is a duplicate -- I haven't seen it show up on the list, so I'm resending from the address that I subscribed with. ]
Hi all.
I just started using xmonad, and there's a layout I want to have but can't quite figure out how to get. I'm sure it's just a matter of gluing the right pieces from the contrib library together, but I haven't gotten it right yet.
I want the workspace to be divided vertically into two areas. Each area should show just one window at a time. Pressing Alt-Tab (or something) should cycle through, in the currently focused half of the screen, all windows except the one that's visible in the other area. The idea being that visible but non-focused windows should stay visible and non-focused.
For example, assume the workspace has five windows, A through E, with C and E currently visible. Alt-Tabbing when the focus is on the left half of the workspace should cycle through A, B, C, and D; if the right half is focused, we should cycle through A, B, D, and E.
XMonad.Actions.CycleWS lets me do exactly this with workspaces and two Xinerama screens, by binding (moveTo Next HiddenNonEmptyWS) to a key.
XMonad.Layout.TwoPane is similar to what you want, maybe you could hack it a bit. Jeremy

On Mon, Jan 19, 2009 at 9:24 AM, Karl Hasselström < kha-xmonad@hemma.treskal.com> wrote:
I want the workspace to be divided vertically into two areas. Each area should show just one window at a time. Pressing Alt-Tab (or something) should cycle through, in the currently focused half of the screen, all windows except the one that's visible in the other area. The idea being that visible but non-focused windows should stay visible and non-focused.
For example, assume the workspace has five windows, A through E, with C and E currently visible. Alt-Tabbing when the focus is on the left half of the workspace should cycle through A, B, C, and D; if the right half is focused, we should cycle through A, B, D, and E.
So far as I know, no, there are no modules providing everything you need. As Jeremy pointed out TwoPane is very close. You inspired me to at least try to fill in the missing bits, since I've been using TwoPane more on laptop. Attached is an xmonad.hs with some functions to cycle all the unfocused windows toward or away from the master window. The nextUnfocused/prevUnfocused functions should work on any layout afaik, although with focusFollowsMouse = True they can be a bit strange. You need to keep the mouse over the 'stable' window while cycling unfocused, or focus jumps to the window the mouse is over and you rapidly scramble your windows. This is not much of an issue with TwoPane, but for other layouts not so nice. Maybe someone more knowledgable can point out a better way or how to prevent this focus changing. regards, Wirt

On 2009-01-21 08:50:14 -0700, Wirt Wolff wrote:
-- cycle unfocused windows toward the master doing nothing on empty workspaces nextUnfocused :: X () nextUnfocused = windows $ W.modify' towardMaster
-- cycle unfocused windows away from the master doing nothing on empty workspaces prevUnfocused :: X () prevUnfocused = windows $ W.modify' awayFromMaster
-- cycle unfocused toward master on a Stack towardMaster:: W.Stack a -> W.Stack a towardMaster(W.Stack t [] rs) = case rs of [] -> W.Stack t [] rs x:xs -> W.Stack t [] (xs ++ [x]) towardMaster(W.Stack t ls rs) = case rs of [] -> W.Stack t (reverse $ vs ++ [v]) [] x:xs -> W.Stack t (reverse $ vs ++ [x]) (xs ++ [v]) where (v:vs) = reverse ls
-- cycle unfocused away from master on a Stack awayFromMaster :: W.Stack a -> W.Stack a awayFromMaster = reverseStack . towardMaster . reverseStack where reverseStack (W.Stack t ls rs) = W.Stack t rs ls
Hmm, I'd like to do something like this, but cycle through the windows that are currently not _visible_. I've looked through the documentation, but I can't find any way to tell if a given window is currently visible. -- Karl Hasselström, kha@treskal.com www.treskal.com/kalle

On 2009-01-21 23:06:29 +0100, Karl Hasselström wrote:
Hmm, I'd like to do something like this, but cycle through the windows that are currently not _visible_. I've looked through the documentation, but I can't find any way to tell if a given window is currently visible.
OK, I got it working. With this, add Sliced 2 Nothing [] to your layouts, and bind a suitable key to focusNextUnmapped and you're ready to go! At most two windows are shown at a time, and the focusNextUnmapped key will cycle through the hidden windows in the currently focused position, leaving the rest of the visible windows alone. I'll happily accept tips on making this code less ugly -- this is the first useful piece of Haskell code I've ever written ... -+- data (Show a, Read a) => Sliced a = Sliced Int -- number of windows visible (Maybe a) -- focused window [Maybe a] -- visible windows deriving (Show, Read) fillInBlanks :: [Maybe a] -> [a] -> [Maybe a] fillInBlanks [] _ = [] fillInBlanks xs [] = xs fillInBlanks ((Just x):xs) ys = (Just x):(fillInBlanks xs ys) fillInBlanks (Nothing:xs) (y:ys) = (Just y):(fillInBlanks xs ys) instance (Eq a, Show a, Read a) => LayoutClass Sliced a where doLayout (Sliced numVisible focused visible) rect st = return (tile, Just $ next) where wasFocused w = case focused of Just f -> w == f Nothing -> False fixLength v = take numVisible $ v ++ noth where noth = Nothing : noth switchToNewFocused v = if (Just $ SS.focus st) `elem` v then v else map repl v where repl Nothing = Nothing repl (Just w) = Just (if wasFocused w then (SS.focus st) else w) replaceEmptyWithFocused v = if (Just $ SS.focus st) `elem` v then v else fillInBlanks v [SS.focus st] replaceRightmostWithFocused v = if (Just $ SS.focus st) `elem` v then v else reverse $ (Just $ SS.focus st) : (tail $ reverse v) removeDeleted v = map filt v where filt Nothing = Nothing filt (Just w) = if w `elem` (SS.integrate st) then (Just w) else Nothing fillEmptySlots v = fillInBlanks v hidden where hidden = filter (`notElem` (catMaybes v)) (SS.integrate st) visible' = fillEmptySlots $ removeDeleted $ replaceRightmostWithFocused $ replaceEmptyWithFocused $ switchToNewFocused $ fixLength visible tile = zip toDraw $ splitHorizontally (length toDraw) rect where toDraw = catMaybes visible' next = Sliced numVisible (Just $ SS.focus st) visible' handleMessage (Sliced numVisible focused visible) x = return $ case fromMessage x of Just Shrink -> Just (Sliced (numVisible - 1) focused visible) Just Expand -> Just (Sliced (numVisible + 1) focused visible) _ -> Nothing description _ = "Sliced" -- Shift focus one step. shiftOne :: SS.Stack a -> SS.Stack a shiftOne (SS.Stack t ls (r:rs)) = SS.Stack r (t:ls) rs shiftOne (SS.Stack t ls []) = SS.Stack x [] xs where (x:xs) = reverse (t:ls) -- Shift focus to next unmapped window. focusNextUnmapped :: X () focusNextUnmapped = do state <- get let visible = mapped state Op.windows $ SS.modify' $ skipWindows visible where skipWindows wins st@(SS.Stack t _ _) = if S.member t wins then skipWindows wins' st' else st where wins' = S.delete t wins st' = shiftOne st -- Karl Hasselström, kha@treskal.com www.treskal.com/kalle

On Thu, Jan 22, 2009 at 04:50:23AM +0100, Karl Hasselström wrote:
On 2009-01-21 23:06:29 +0100, Karl Hasselström wrote:
Hmm, I'd like to do something like this, but cycle through the windows that are currently not _visible_. I've looked through the documentation, but I can't find any way to tell if a given window is currently visible.
OK, I got it working. With this, add
Sliced 2 Nothing []
to your layouts, and bind a suitable key to
focusNextUnmapped
and you're ready to go! At most two windows are shown at a time, and the focusNextUnmapped key will cycle through the hidden windows in the currently focused position, leaving the rest of the visible windows alone.
I'll happily accept tips on making this code less ugly -- this is the first useful piece of Haskell code I've ever written ...
Cool, why not make this into a proper module and submit a patch? See http://haskell.org/haskellwiki/Xmonad/xmonad_development_tutorial for a tutorial on how to do this. -Brent
participants (4)
-
Brent Yorgey
-
Jeremy Apthorp
-
Karl Hasselström
-
Wirt Wolff