From b84cd8cf7dbe9ccb8837752b73acf132ee59d1e4 Mon Sep 17 00:00:00 2001 From: Andrea Rossato Date: Fri, 22 Feb 2008 18:58:15 +0100 Subject: runLayout is now a LayoutClass method and takes the Workspace and the screen Rectangle darcs-hash:20080222175815-32816-e3893760e1024bcbf30a4fbb71ca7c2b4d8bb403.gz --- XMonad/Core.hs | 14 +++++++------- XMonad/Operations.hs | 10 +++++----- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/XMonad/Core.hs b/XMonad/Core.hs index 89e6ab2..32fc234 100644 --- a/XMonad/Core.hs +++ b/XMonad/Core.hs @@ -23,7 +23,7 @@ module XMonad.Core ( ScreenId(..), ScreenDetail(..), XState(..), XConf(..), XConfig(..), LayoutClass(..), Layout(..), readsLayout, Typeable, Message, - SomeMessage(..), fromMessage, runLayout, LayoutMessages(..), + SomeMessage(..), fromMessage, LayoutMessages(..), runX, catchX, userCode, io, catchIO, doubleFork, withDisplay, withWindowSet, isRoot, runOnWorkspaces, broadcastMessage, getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX, @@ -206,6 +206,11 @@ readsLayout (Layout l) s = [(Layout (asTypeOf x l), rs) | (x, rs) <- reads s] -- class Show (layout a) => LayoutClass layout a where + -- | This calls doLayout if there are any windows to be laid out, and + -- emptyLayout otherwise. + runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a)) + runLayout (Workspace _ l ms) r = maybe (emptyLayout l r) (doLayout l r) ms + -- | Given a Rectangle in which to place the windows, and a Stack -- of windows, return a list of windows and their corresponding -- Rectangles. If an element is not given a Rectangle by @@ -231,7 +236,6 @@ class Show (layout a) => LayoutClass layout a where -- 'handleMessage' returns Nothing, then the layout did not respond to -- that message and the screen is not refreshed. Otherwise, 'handleMessage' -- returns an updated 'Layout' and the screen is refreshed. - -- handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a)) handleMessage l = return . pureMessage l @@ -246,6 +250,7 @@ class Show (layout a) => LayoutClass layout a where description = show instance LayoutClass Layout Window where + runLayout (Workspace i (Layout l) ms) r = fmap (fmap Layout) `fmap` runLayout (Workspace i l ms) r doLayout (Layout l) r s = fmap (fmap Layout) `fmap` doLayout l r s emptyLayout (Layout l) r = fmap (fmap Layout) `fmap` emptyLayout l r handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l @@ -253,11 +258,6 @@ instance LayoutClass Layout Window where instance Show (Layout a) where show (Layout l) = show l --- | This calls doLayout if there are any windows to be laid out, and --- emptyLayout otherwise. -runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a)) -runLayout l r = maybe (emptyLayout l r) (doLayout l r) - -- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/, -- Simon Marlow, 2006. Use extensible messages to the handleMessage handler. -- diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs index e95593e..9d6164b 100644 --- a/XMonad/Operations.hs +++ b/XMonad/Operations.hs @@ -128,10 +128,10 @@ windows f = do 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 - let n = W.tag (W.workspace w) - this = W.view n ws - l = W.layout (W.workspace w) - flt = filter (flip M.member (W.floating ws)) (W.index this) + 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) @@ -142,7 +142,7 @@ windows f = do -- just the tiled windows: -- now tile the windows on this workspace, modified by the gap - (rs, ml') <- runLayout l viewrect tiled `catchX` runLayout (Layout Full) viewrect tiled + (rs, ml') <- runLayout wsp { W.stack = tiled } viewrect`catchX` runLayout wsp { W.layout = Layout Full, W.stack = tiled } viewrect mapM_ (uncurry tileWindow) rs whenJust ml' $ \l' -> runOnWorkspaces (\ww -> if W.tag ww == n then return $ ww { W.layout = l'} -- cgit v1.2.3