From 2a59314ffa3997b6365bf2130ef8df0e0bc0185d Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Fri, 4 May 2007 06:56:44 +0200 Subject: Handle empty layout lists darcs-hash:20070504045644-a5988-68a6d650bacab936f893b96bf866696da3f73436.gz --- Main.hs | 5 +++-- Operations.hs | 15 ++++++++------- XMonad.hs | 3 ++- 3 files changed, 13 insertions(+), 10 deletions(-) diff --git a/Main.hs b/Main.hs index 33812ef..ae0b596 100644 --- a/Main.hs +++ b/Main.hs @@ -45,7 +45,8 @@ main = do nbc <- initcolor normalBorderColor fbc <- initcolor focusedBorderColor - let cf = XConf + let safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs) + cf = XConf { display = dpy , xineScreens = xinesc , theRoot = rootw @@ -59,7 +60,7 @@ main = do } st = XState { workspace = W.empty workspaces (length xinesc) - , layouts = M.empty + , layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] } xSetErrorHandler -- in C, I'm too lazy to write the binding diff --git a/Operations.hs b/Operations.hs index ad0bf0c..73e3c1d 100644 --- a/Operations.hs +++ b/Operations.hs @@ -47,8 +47,8 @@ refresh = do XConf { xineScreens = xinesc, display = d } <- ask -- neat, eh? flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do - let sc = genericIndex xinesc scn -- temporary coercion! - l = fromMaybe full (do (x:_) <- M.lookup n fls; return x) + let sc = genericIndex xinesc scn -- temporary coercion! + (Just l) = fmap fst $ M.lookup n fls mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $ (doLayout l) sc $ W.index n ws whenJust (W.peekStack n ws) (io . raiseWindow d) whenJust (W.peek ws) setFocus @@ -73,7 +73,8 @@ clearEnterEvents = do -- uppermost. -- switchLayout :: X () -switchLayout = layout (\(x:xs) -> xs ++ [x]) -- TODO pattern match here might fail! +switchLayout = layout (\(x, xs) -> let xs' = xs ++ [x] + in (head xs', tail xs')) -- -- TODO, using Typeable for extensible stuff is a bit gunky. Check -- @@ -85,7 +86,7 @@ switchLayout = layout (\(x:xs) -> xs ++ [x]) -- TODO pattern match here might fa data ShrinkOrExpand = Shrink | Expand deriving (Typeable, Eq) layoutMsg :: Typeable a => a -> X () -- FIXME: The below shouldn't refresh on Nothing -layoutMsg a = layout $ \x@(l:ls) -> maybe x (:ls) (modifyLayout l (toDyn a)) +layoutMsg a = layout $ \x@(l, ls) -> maybe x (flip (,) ls) (modifyLayout l (toDyn a)) -- -- Standard layout algorithms: @@ -139,11 +140,11 @@ tile r (Rectangle sx sy sw sh) (w:s) = -- | layout. Modify the current workspace's layout with a pure -- function and refresh. -layout :: ([Layout] -> [Layout]) -> X () +layout :: ((Layout, [Layout]) -> (Layout, [Layout])) -> X () layout f = do modify $ \s -> - let n = W.current . workspace $ s - fl = M.findWithDefault defaultLayouts n $ layouts s + let n = W.current . workspace $ s + (Just fl) = M.lookup n $ layouts s in s { layouts = M.insert n (f fl) (layouts s) } refresh diff --git a/XMonad.hs b/XMonad.hs index 1f602c8..8293212 100644 --- a/XMonad.hs +++ b/XMonad.hs @@ -36,7 +36,8 @@ import qualified Data.Map as M -- Just the display, width, height and a window list data XState = XState { workspace :: !WindowSet -- ^ workspace list - , layouts :: !(M.Map WorkspaceId [Layout]) -- ^ mapping of workspaces + , layouts :: !(M.Map WorkspaceId (Layout, [Layout])) + -- ^ mapping of workspaces -- to descriptions of their layouts } -- cgit v1.2.3