aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/LayoutModifier.hs
diff options
context:
space:
mode:
authorDaniel Schoepe <daniel.schoepe@gmail.com>2009-08-22 23:39:58 +0200
committerDaniel Schoepe <daniel.schoepe@gmail.com>2009-08-22 23:39:58 +0200
commitd969f65c194346e045bd1ccf99866d6333cacc98 (patch)
tree4580c839e36fa031764e49c15e447cd836dd6f3b /XMonad/Layout/LayoutModifier.hs
parent388d343511cfe7cc5e522b4350b1ad3bc9c8fd6c (diff)
downloadXMonadContrib-d969f65c194346e045bd1ccf99866d6333cacc98.tar.gz
XMonadContrib-d969f65c194346e045bd1ccf99866d6333cacc98.tar.xz
XMonadContrib-d969f65c194346e045bd1ccf99866d6333cacc98.zip
Add a way to update the modifier in X.L.LayoutModifier
Ignore-this: f257a376bef57689287b68ed21ec903d This patch adds the possibility to update the state of a layout modifier when modifying the underlying layout before it is run(i.e. using modifyLayout). The modified state is also passed to the subsequent call of redoLayout, whose return takes precedence if both functions return modified states of the layout modifier. darcs-hash:20090822213958-7f603-2116263ba9622458aa9dea0f664af4431775a361.gz
Diffstat (limited to 'XMonad/Layout/LayoutModifier.hs')
-rw-r--r--XMonad/Layout/LayoutModifier.hs24
1 files changed, 21 insertions, 3 deletions
diff --git a/XMonad/Layout/LayoutModifier.hs b/XMonad/Layout/LayoutModifier.hs
index a55444f..a1db7a3 100644
--- a/XMonad/Layout/LayoutModifier.hs
+++ b/XMonad/Layout/LayoutModifier.hs
@@ -29,6 +29,8 @@ module XMonad.Layout.LayoutModifier (
LayoutModifier(..), ModifiedLayout(..)
) where
+import Control.Monad
+
import XMonad
import XMonad.StackSet ( Stack, Workspace (..) )
@@ -106,6 +108,22 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
-> X ([(a, Rectangle)], Maybe (l a))
modifyLayout _ w r = runLayout w r
+ -- | Similar to 'modifyLayout', but this function also allows you
+ -- update the state of your layout modifier(the second value in the
+ -- outer tuple).
+ --
+ -- If both 'modifyLayoutWithUpdate' and 'redoLayout' return a
+ -- modified state of the layout modifier, 'redoLayout' takes
+ -- precedence. If this function returns a modified state, this
+ -- state will internally be used in the subsequent call to
+ -- 'redoLayout' as well.
+ modifyLayoutWithUpdate :: (LayoutClass l a) =>
+ m a
+ -> Workspace WorkspaceId (l a) a
+ -> Rectangle
+ -> X (([(a,Rectangle)], Maybe (l a)), Maybe (m a))
+ modifyLayoutWithUpdate m w r = flip (,) Nothing `fmap` modifyLayout m w r
+
-- | 'handleMess' allows you to spy on messages to the underlying
-- layout, in order to have an effect in the X monad, or alter
-- the layout modifier state in some way (by returning @Just
@@ -234,9 +252,9 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
-- semantics of a 'LayoutModifier' applied to an underlying layout.
instance (LayoutModifier m a, LayoutClass l a) => LayoutClass (ModifiedLayout m l) a where
runLayout (Workspace i (ModifiedLayout m l) ms) r =
- do (ws, ml') <- modifyLayout m (Workspace i l ms) r
- (ws', mm') <- redoLayout m r ms ws
- let ml'' = case mm' of
+ do ((ws, ml'),mm') <- modifyLayoutWithUpdate m (Workspace i l ms) r
+ (ws', mm'') <- redoLayout (maybe m id mm') r ms ws
+ let ml'' = case mm'' `mplus` mm' of
Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
Nothing -> ModifiedLayout m `fmap` ml'
return (ws', ml'')