aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-23 08:56:10 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-23 08:56:10 +0100
commit729c6e4456f9184b575edaa97cbb3616e3388a90 (patch)
tree022086f865173017cf69a0534e63b3c3fc713ada
parent8fe9bce455127ba0825607851bc207cfe0c0e210 (diff)
downloadXMonadContrib-729c6e4456f9184b575edaa97cbb3616e3388a90.tar.gz
XMonadContrib-729c6e4456f9184b575edaa97cbb3616e3388a90.tar.xz
XMonadContrib-729c6e4456f9184b575edaa97cbb3616e3388a90.zip
LayoutModifier: reimplement ModifiedLayout using runLayout and more
- change modifyLayout type to get the Workspace - updated ResizeScreen and ManageDocks accordingly. darcs-hash:20080223075610-32816-05f373cf73305ce5b41d0c250fb5d6413e72b3b4.gz
-rw-r--r--XMonad/Hooks/ManageDocks.hs4
-rw-r--r--XMonad/Layout/LayoutModifier.hs28
-rw-r--r--XMonad/Layout/ResizeScreen.hs4
3 files changed, 16 insertions, 20 deletions
diff --git a/XMonad/Hooks/ManageDocks.hs b/XMonad/Hooks/ManageDocks.hs
index d971e7c..f1c1d54 100644
--- a/XMonad/Hooks/ManageDocks.hs
+++ b/XMonad/Hooks/ManageDocks.hs
@@ -122,9 +122,9 @@ data ToggleStruts = ToggleStruts deriving (Read,Show,Typeable)
instance Message ToggleStruts
instance LayoutModifier AvoidStruts a where
- modifyLayout (AvoidStruts b) l r s = do
+ modifyLayout (AvoidStruts b) w r = do
nr <- if b then fmap ($ r) calcGap else return r
- doLayout l nr s
+ runLayout w nr
handleMess (AvoidStruts b ) m
| Just ToggleStruts <- fromMessage m = return $ Just $ AvoidStruts (not b)
diff --git a/XMonad/Layout/LayoutModifier.hs b/XMonad/Layout/LayoutModifier.hs
index d92f6c4..d1f8b04 100644
--- a/XMonad/Layout/LayoutModifier.hs
+++ b/XMonad/Layout/LayoutModifier.hs
@@ -21,7 +21,7 @@ module XMonad.Layout.LayoutModifier (
) where
import XMonad
-import XMonad.StackSet ( Stack )
+import XMonad.StackSet ( Stack, Workspace (..) )
-- $usage
-- Use LayoutModifier to help write easy Layouts.
@@ -33,9 +33,9 @@ import XMonad.StackSet ( Stack )
-- "XMonad.Layout.Magnifier", "XMonad.Layout.NoBorder",
class (Show (m a), Read (m a)) => LayoutModifier m a where
- modifyLayout :: (LayoutClass l a) => m a -> l a -> Rectangle
- -> Stack a -> X ([(a, Rectangle)], Maybe (l a))
- modifyLayout _ l r s = doLayout l r s
+ modifyLayout :: (LayoutClass l a) => m a -> Workspace WorkspaceId (l a) a
+ -> Rectangle -> X ([(a, Rectangle)], Maybe (l a))
+ modifyLayout _ w r = runLayout w r
handleMess :: m a -> SomeMessage -> X (Maybe (m a))
handleMess m mess | Just Hide <- fromMessage mess = doUnhook
| Just ReleaseResources <- fromMessage mess = doUnhook
@@ -67,20 +67,16 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
x <> y = x ++ " " ++ y
instance (LayoutModifier m a, LayoutClass l a) => LayoutClass (ModifiedLayout m l) a where
- doLayout (ModifiedLayout m l) r s =
- do (ws, ml') <- modifyLayout m l r s
- (ws', mm') <- redoLayout m r s ws
+ runLayout (Workspace i (ModifiedLayout m l) ms) r =
+ do (ws, ml') <- modifyLayout m (Workspace i l ms) r
+ (ws', mm') <- case ms of
+ Just s -> redoLayout m r s ws
+ Nothing -> emptyLayoutMod m r ws
let ml'' = case mm' of
- Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
- Nothing -> ModifiedLayout m `fmap` ml'
- return (ws', ml'')
- emptyLayout (ModifiedLayout m l) r =
- do (ws, ml') <- emptyLayout l r
- (ws',mm') <- emptyLayoutMod m r ws
- let ml'' = case mm' of
- Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
- Nothing -> ModifiedLayout m `fmap` ml'
+ Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
+ Nothing -> ModifiedLayout m `fmap` ml'
return (ws', ml'')
+
handleMessage (ModifiedLayout m l) mess =
do mm' <- handleMessOrMaybeModifyIt m mess
ml' <- case mm' of
diff --git a/XMonad/Layout/ResizeScreen.hs b/XMonad/Layout/ResizeScreen.hs
index 54de481..bcbab19 100644
--- a/XMonad/Layout/ResizeScreen.hs
+++ b/XMonad/Layout/ResizeScreen.hs
@@ -63,14 +63,14 @@ data ResizeScreen a = ResizeScreen ResizeMode Int
data ResizeMode = T | B | L | R deriving (Read, Show)
instance LayoutModifier ResizeScreen a where
- modifyLayout m l rect@(Rectangle x y w h) s
+ modifyLayout m ws rect@(Rectangle x y w h)
| ResizeScreen L i <- m = resize $ Rectangle (x + fi i) y (w - fi i) h
| ResizeScreen R i <- m = resize $ Rectangle x y (w - fi i) h
| ResizeScreen T i <- m = resize $ Rectangle x (y + fi i) w (h - fi i)
| ResizeScreen B i <- m = resize $ Rectangle x y w (h - fi i)
| WithNewScreen r <- m = resize r
| otherwise = resize rect
- where resize nr = doLayout l nr s
+ where resize nr = runLayout ws nr
pureMess (ResizeScreen d _) m
| Just (SetTheme t) <- fromMessage m = Just $ ResizeScreen d (fi $ decoHeight t)