aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-09-25 20:29:30 +0200
committerDavid Roundy <droundy@darcs.net>2007-09-25 20:29:30 +0200
commit5d42da6f605385a5692eaf34678e6d4524edad56 (patch)
tree13e15aec0414303d7f0a25aa2d074811a2947059
parent76b62aa4f8b75b704e4e34fe4c7fe536a2e6d1ea (diff)
downloadXMonadContrib-5d42da6f605385a5692eaf34678e6d4524edad56.tar.gz
XMonadContrib-5d42da6f605385a5692eaf34678e6d4524edad56.tar.xz
XMonadContrib-5d42da6f605385a5692eaf34678e6d4524edad56.zip
modifyLayout -> handleMessage.
darcs-hash:20070925182930-72aca-7941d37cac143444e9f167e3dd15944d1138a377.gz
-rw-r--r--Combo.hs4
-rw-r--r--LayoutModifier.hs4
-rw-r--r--NewTabbed.hs2
-rw-r--r--ThreeColumns.hs2
-rw-r--r--TwoPane.hs2
5 files changed, 7 insertions, 7 deletions
diff --git a/Combo.hs b/Combo.hs
index 1823410..67263e2 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -79,7 +79,7 @@ instance (Eq a, Show a, Read a, ReadableSomeLayout a, Layout l (SomeLayout a, In
, down = tail $ dropWhile (/=z) xs }
| otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs
- modifyLayout (Combo f super origls) m =
+ handleMessage (Combo f super origls) m =
do mls <- broadcastPrivate m (map fst origls)
let mls' = (\x->zipWith first (map const x) origls) `fmap` mls
msuper <- broadcastPrivate m [super]
@@ -92,4 +92,4 @@ broadcastPrivate a ol = do nml <- mapM f ol
if any isJust nml
then return $ Just $ zipWith ((flip maybe) id) ol nml
else return Nothing
- where f l = modifyLayout l a `catchX` return Nothing
+ where f l = handleMessage l a `catchX` return Nothing
diff --git a/LayoutModifier.hs b/LayoutModifier.hs
index bc82a14..f2dcd32 100644
--- a/LayoutModifier.hs
+++ b/LayoutModifier.hs
@@ -45,8 +45,8 @@ instance (LayoutModifier m a, Layout l a) => Layout (ModifiedLayout m l) a where
Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
Nothing -> ModifiedLayout m `fmap` ml'
return (ws', ml'')
- modifyLayout (ModifiedLayout m l) mess =
- do ml' <- modifyLayout l mess
+ handleMessage (ModifiedLayout m l) mess =
+ do ml' <- handleMessage l mess
mm' <- modifyModify m mess
return $ case mm' of
Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
diff --git a/NewTabbed.hs b/NewTabbed.hs
index 3312b48..73d5a1b 100644
--- a/NewTabbed.hs
+++ b/NewTabbed.hs
@@ -95,7 +95,7 @@ data Tabbed a =
instance Layout Tabbed Window where
doLayout (Tabbed mst conf) = doLay mst conf
- modifyLayout l m = modLay l m
+ handleMessage l m = modLay l m
instance Read FontStruct where
readsPrec _ _ = []
diff --git a/ThreeColumns.hs b/ThreeColumns.hs
index 520f703..66862c3 100644
--- a/ThreeColumns.hs
+++ b/ThreeColumns.hs
@@ -48,7 +48,7 @@ instance Layout ThreeCol a where
doLayout (ThreeCol nmaster _ frac) r =
return . (\x->(x,Nothing)) .
ap zip (tile3 frac r nmaster . length) . W.integrate
- modifyLayout (ThreeCol nmaster delta frac) m =
+ handleMessage (ThreeCol nmaster delta frac) m =
return $ msum [fmap resize (fromMessage m)
,fmap incmastern (fromMessage m)]
where resize Shrink = ThreeCol nmaster delta (max 0 $ frac-delta)
diff --git a/TwoPane.hs b/TwoPane.hs
index 0a3f0d5..90c4f13 100644
--- a/TwoPane.hs
+++ b/TwoPane.hs
@@ -51,7 +51,7 @@ instance Layout TwoPane a where
[] -> [(focus st, rect)]
where (left, right) = splitHorizontallyBy split rect
- modifyLayout (TwoPane delta split) x =
+ handleMessage (TwoPane delta split) x =
return $ case fromMessage x of
Just Shrink -> Just (TwoPane delta (split - delta))
Just Expand -> Just (TwoPane delta (split + delta))