summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorSpencer Janssen <spencerjanssen@gmail.com>2008-11-18 08:44:47 +0100
committerSpencer Janssen <spencerjanssen@gmail.com>2008-11-18 08:44:47 +0100
commit3194a4ec820e53cdb370403503871ff4efb3f9e1 (patch)
treef747424c009fab809a1e1cf5a7d19aa5186f91e1 /XMonad
parent699980621be39057f6eaeb2440c4794a89b35eb4 (diff)
downloadmetatile-3194a4ec820e53cdb370403503871ff4efb3f9e1.tar
metatile-3194a4ec820e53cdb370403503871ff4efb3f9e1.zip
Tile all windows at once
darcs-hash:20081118074447-25a6b-fc9fe14d2a2ad88884fe2f87548d2f35720e8841
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Operations.hs20
1 files changed, 11 insertions, 9 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index 6d6b04c..ba9c774 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -124,11 +124,10 @@ windows f = do
-- for each workspace, layout the currently visible workspaces
let allscreens = W.screens ws
summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
- visible <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
+ rects <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
let wsp = W.workspace w
this = W.view n ws
n = W.tag wsp
- flt = filter (flip M.member (W.floating ws)) (W.index this)
tiled = (W.stack . W.workspace . W.current $ this)
>>= W.filter (`M.notMember` W.floating ws)
>>= W.filter (`notElem` vis)
@@ -138,19 +137,22 @@ windows f = do
-- now tile the windows on this workspace, modified by the gap
(rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
- mapM_ (uncurry tileWindow) rs
updateLayout n ml'
- -- now the floating windows:
- -- move/resize the floating windows, if there are any
- forM_ flt $ \fw -> whenJust (M.lookup fw (W.floating ws)) $
- \r -> tileWindow fw $ scaleRationalRect viewrect r
+ let m = W.floating ws
+ flt = [(fw, scaleRationalRect viewrect r)
+ | fw <- filter (flip M.member m) (W.index this)
+ , Just r <- [M.lookup fw m]]
+ vs = flt ++ rs
- let vs = flt ++ map fst rs
- io $ restackWindows d vs
+ io $ restackWindows d (map fst vs)
-- return the visible windows for this workspace:
return vs
+ let visible = map fst rects
+
+ mapM_ (uncurry tileWindow) rects
+
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
asks (logHook . config) >>= userCode