aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPeter Jones <pjones@devalot.com>2015-03-10 00:29:39 +0100
committerPeter Jones <pjones@devalot.com>2015-03-10 00:29:39 +0100
commit78ca555fc0096b584c615724a4676ce53d85f58c (patch)
tree6320af936ec3409b2c92366d4f39590f5c7dfe79
parent81d4a4235c295c1c06811a4d03903d08450883f6 (diff)
downloadXMonadContrib-78ca555fc0096b584c615724a4676ce53d85f58c.tar.gz
XMonadContrib-78ca555fc0096b584c615724a4676ce53d85f58c.tar.xz
XMonadContrib-78ca555fc0096b584c615724a4676ce53d85f58c.zip
Add the ability to specify padding used with Maximize
Ignore-this: 71ac5db4513da0b7a45eb82ec184f4e3 darcs-hash:20150309232939-fd82d-9b23314e9b125c4081242c5fe5fd7f9ed8795558.gz
-rw-r--r--XMonad/Layout/Maximize.hs38
1 files changed, 26 insertions, 12 deletions
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index 589b962..4abb12b 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -19,6 +19,7 @@ module XMonad.Layout.Maximize (
-- * Usage
-- $usage
maximize,
+ maximizeWithPadding,
maximizeRestore,
Maximize, MaximizeRestore,
) where
@@ -35,7 +36,13 @@ import Data.List ( partition )
--
-- Then edit your @layoutHook@ by adding the Maximize layout modifier:
--
--- > myLayout = maximize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
+-- > myLayout = maximize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..)
+-- > main = xmonad def { layoutHook = myLayout }
+--
+-- Or, if you want to control the amount of padding placed around the
+-- maximized window:
+--
+-- > myLayout = maximizeWithPadding 10 (Tall 1 (3/100) (1/2)) ||| Full ||| etc..)
-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see:
@@ -51,9 +58,14 @@ import Data.List ( partition )
--
-- "XMonad.Doc.Extending#Editing_key_bindings".
-data Maximize a = Maximize (Maybe Window) deriving ( Read, Show )
+data Maximize a = Maximize Dimension (Maybe Window) deriving ( Read, Show )
maximize :: LayoutClass l Window => l Window -> ModifiedLayout Maximize l Window
-maximize = ModifiedLayout $ Maximize Nothing
+maximize = ModifiedLayout $ Maximize 25 Nothing
+
+-- | Like 'maximize', but allows you to specify the amount of padding
+-- placed around the maximized window.
+maximizeWithPadding :: LayoutClass l Window => Dimension -> l Window -> ModifiedLayout Maximize l Window
+maximizeWithPadding padding = ModifiedLayout $ Maximize padding Nothing
data MaximizeRestore = MaximizeRestore Window deriving ( Typeable, Eq )
instance Message MaximizeRestore
@@ -61,26 +73,28 @@ maximizeRestore :: Window -> MaximizeRestore
maximizeRestore = MaximizeRestore
instance LayoutModifier Maximize Window where
- modifierDescription (Maximize _) = "Maximize"
- pureModifier (Maximize (Just target)) rect (Just (S.Stack focused _ _)) wrs =
+ modifierDescription (Maximize _ _) = "Maximize"
+ pureModifier (Maximize padding (Just target)) rect (Just (S.Stack focused _ _)) wrs =
if focused == target
then (maxed ++ rest, Nothing)
else (rest ++ maxed, lay)
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)
- lay | null maxed = Just (Maximize Nothing)
+ maxRect = Rectangle (rect_x rect + fromIntegral padding)
+ (rect_y rect + fromIntegral padding)
+ (rect_width rect - padding * 2)
+ (rect_height rect - padding * 2)
+ lay | null maxed = Just (Maximize padding Nothing)
| otherwise = Nothing
pureModifier _ _ _ wrs = (wrs, Nothing)
- pureMess (Maximize mw) m = case fromMessage m of
+ pureMess (Maximize padding mw) m = case fromMessage m of
Just (MaximizeRestore w) -> case mw of
Just w' -> if (w == w')
- then Just $ Maximize Nothing -- restore window
- else Just $ Maximize $ Just w -- maximize different window
- Nothing -> Just $ Maximize $ Just w -- maximize window
+ then Just $ Maximize padding Nothing -- restore window
+ else Just $ Maximize padding $ Just w -- maximize different window
+ Nothing -> Just $ Maximize padding $ Just w -- maximize window
_ -> Nothing
-- vim: sw=4:et