aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-05-03 02:10:52 +0200
committerJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-05-03 02:10:52 +0200
commit354eac8b9cc9f31c4955f9802648a894747b010a (patch)
treed118ab211008924ae308e54476366d90c35ada5a /XMonad/Layout
parent76c329851a4e14f03d73ddf026c69b16cb47e783 (diff)
downloadXMonadContrib-354eac8b9cc9f31c4955f9802648a894747b010a.tar.gz
XMonadContrib-354eac8b9cc9f31c4955f9802648a894747b010a.tar.xz
XMonadContrib-354eac8b9cc9f31c4955f9802648a894747b010a.zip
Expanded on X.L.Maximize functionality
Ignore-this: b0d765b3bf6fc1e72cedebfd564236fc 1. Move maximized window into the background when it's not focused. 2. Changed semantics so that maximizing a different window will automatically restore the currently maximized window and maximize the new one (previously this had to be done in two seperate steps). darcs-hash:20090503001052-594c5-14c03dbf16c39241cedc54854332231eee78047a.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/Maximize.hs27
1 files changed, 16 insertions, 11 deletions
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index febef18..3495ef1 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -23,6 +23,7 @@ module XMonad.Layout.Maximize (
) where
import XMonad
+import qualified XMonad.StackSet as S
import XMonad.Layout.LayoutModifier
import Data.List ( partition )
@@ -60,19 +61,23 @@ maximizeRestore = MaximizeRestore
instance LayoutModifier Maximize Window where
modifierDescription (Maximize _) = "Maximize"
- redoLayout (Maximize mw) rect _ wrs = case mw of
- Just win ->
- return (maxed ++ rest, Nothing)
- where
- maxed = map (\(w, _) -> (w, maxRect)) toMax
- (toMax, rest) = partition (\(w, _) -> w == win) wrs
- maxRect = Rectangle (rect_x rect + 50) (rect_y rect + 50)
- (rect_width rect - 100) (rect_height rect - 100)
- Nothing -> return (wrs, Nothing)
+ pureModifier (Maximize (Just target)) rect (Just (S.Stack focused _ _)) wrs =
+ if focused == target
+ then (maxed ++ rest, Nothing)
+ else (rest ++ maxed, Nothing)
+ where
+ (toMax, rest) = partition (\(w, _) -> w == target) wrs
+ maxed = map (\(w, _) -> (w, maxRect)) toMax
+ maxRect = Rectangle (rect_x rect + 25) (rect_y rect + 25)
+ (rect_width rect - 50) (rect_height rect - 50)
+ pureModifier _ _ _ wrs = (wrs, Nothing)
+
handleMess (Maximize mw) m = case fromMessage m of
Just (MaximizeRestore w) -> case mw of
- Just _ -> return $ Just $ Maximize Nothing
- Nothing -> return $ Just $ Maximize $ Just w
+ Just w' -> if (w == w')
+ then return $ Just $ Maximize Nothing -- restore window
+ else return $ Just $ Maximize $ Just w -- maximize different window
+ Nothing -> return $ Just $ Maximize $ Just w -- maximize window
_ -> return Nothing
-- vim: sw=4:et