From b36d9ed15ccb87a7109aed86e30e2ef0fdd590d9 Mon Sep 17 00:00:00 2001 From: David Roundy Date: Sat, 12 May 2007 23:53:01 +0200 Subject: put doLayout in the X monad. darcs-hash:20070512215301-72aca-59213ac37c38e57d6ffed1d518afd4729f1744c9.gz --- Operations.hs | 10 ++++++---- XMonad.hs | 2 +- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/Operations.hs b/Operations.hs index c890bd5..93fdba1 100644 --- a/Operations.hs +++ b/Operations.hs @@ -48,7 +48,9 @@ refresh = do flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do let sc = genericIndex xinesc scn -- temporary coercion! (Just l) = fmap fst $ M.lookup n fls - whenJust (W.index n ws) $ mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) . doLayout l sc + whenJust (W.index n ws) $ \winds -> + do wrects <- doLayout l sc winds :: X [(Window,Rectangle)] + mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) wrects whenJust (W.peekStack n ws) (io . raiseWindow d) whenJust (W.peek ws) setFocus clearEnterEvents @@ -100,13 +102,13 @@ data Resize = Shrink | Expand deriving Typeable instance Message Resize full :: Layout -full = Layout { doLayout = \sc ws -> [ (w,sc) | w <- ws ] +full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ] , modifyLayout = const Nothing } -- no changes tall, wide :: Rational -> Rational -> Layout wide delta frac = mirrorLayout (tall delta frac) -tall delta frac = Layout { doLayout = tile frac +tall delta frac = Layout { doLayout = \a b -> return $ tile frac a b , modifyLayout = fmap handler . fromMessage } where handler s = tall delta $ (case s of @@ -120,7 +122,7 @@ mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw) -- | Mirror a layout mirrorLayout :: Layout -> Layout mirrorLayout (Layout { doLayout = dl, modifyLayout = ml }) = - Layout { doLayout = \sc -> map (second mirrorRect) . dl (mirrorRect sc) + Layout { doLayout = \sc w -> map (second mirrorRect) `fmap` dl (mirrorRect sc) w , modifyLayout = fmap mirrorLayout . ml } -- | tile. Compute the positions for windows in our default tiling modes diff --git a/XMonad.hs b/XMonad.hs index d996348..22fce97 100644 --- a/XMonad.hs +++ b/XMonad.hs @@ -96,7 +96,7 @@ isRoot w = liftM (w==) (asks theRoot) -- 'doLayout', a pure function to layout a Window set 'modifyLayout', -- 'modifyLayout' can be considered a branch of an exception handler. -- -data Layout = Layout { doLayout :: Rectangle -> [Window] -> [(Window, Rectangle)] +data Layout = Layout { doLayout :: Rectangle -> [Window] -> X [(Window, Rectangle)] , modifyLayout :: SomeMessage -> Maybe Layout } -- Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/, -- cgit v1.2.3