aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorFelix Crux <felixc@felixcrux.com>2014-12-19 23:36:46 +0100
committerFelix Crux <felixc@felixcrux.com>2014-12-19 23:36:46 +0100
commite1fea474888bd42f46e31cb902e3e1175b38d2dd (patch)
tree392a1a28e6e4b682b0dbe8552bdf17732eb2581c
parentf84a11a13e06976dff90f10a75b02a145d404fbe (diff)
downloadXMonadContrib-e1fea474888bd42f46e31cb902e3e1175b38d2dd.tar.gz
XMonadContrib-e1fea474888bd42f46e31cb902e3e1175b38d2dd.tar.xz
XMonadContrib-e1fea474888bd42f46e31cb902e3e1175b38d2dd.zip
Layout.Spacing: Outer window edges now get as much spacing as inner ones
Ignore-this: 61363e97939fe857876c8252ac5f0302 Layout.Spacing applies a customizable amount of space around the outside of each window. At window edges where two windows meet, the total distance between them is therefore twice the customized value (one space value from each window). At the edge of the screen, however, the spacing is only applied once. This results in uneven amounts of spacing and differently-sized gaps on the screen. This patch extends the Spacing layout to include a further gap all around the edge of the screen, thus making all spaces around windows equal in size. darcs-hash:20141219223646-7cf82-41539353bf5af7c54809bb7a9ff1c6a52320aa10.gz
-rw-r--r--XMonad/Layout/Spacing.hs38
1 files changed, 38 insertions, 0 deletions
diff --git a/XMonad/Layout/Spacing.hs b/XMonad/Layout/Spacing.hs
index 609c858..38ffbd5 100644
--- a/XMonad/Layout/Spacing.hs
+++ b/XMonad/Layout/Spacing.hs
@@ -18,12 +18,16 @@ module XMonad.Layout.Spacing (
-- $usage
spacing, Spacing,
+ spacingWithEdge, SpacingWithEdge,
smartSpacing, SmartSpacing,
+ smartSpacingWithEdge, SmartSpacingWithEdge,
) where
import Graphics.X11 (Rectangle(..))
import Control.Arrow (second)
+import XMonad.Core (runLayout)
+import XMonad.StackSet (up, down, Workspace(..))
import XMonad.Util.Font (fi)
import XMonad.Layout.LayoutModifier
@@ -51,6 +55,21 @@ instance LayoutModifier Spacing a where
modifierDescription (Spacing p) = "Spacing " ++ show p
+-- | Surround all windows by a certain number of pixels of blank space, and
+-- additionally adds the same amount of spacing around the edge of the screen.
+spacingWithEdge :: Int -> l a -> ModifiedLayout SpacingWithEdge l a
+spacingWithEdge p = ModifiedLayout (SpacingWithEdge p)
+
+data SpacingWithEdge a = SpacingWithEdge Int deriving (Show, Read)
+
+instance LayoutModifier SpacingWithEdge a where
+
+ pureModifier (SpacingWithEdge p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
+
+ modifyLayout (SpacingWithEdge p) w r = runLayout w (shrinkRect p r)
+
+ modifierDescription (SpacingWithEdge p) = "SpacingWithEdge " ++ show p
+
shrinkRect :: Int -> Rectangle -> Rectangle
shrinkRect p (Rectangle x y w h) = Rectangle (x+fi p) (y+fi p) (w-2*fi p) (h-2*fi p)
@@ -67,3 +86,22 @@ instance LayoutModifier SmartSpacing a where
pureModifier (SmartSpacing p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
modifierDescription (SmartSpacing p) = "SmartSpacing " ++ show p
+
+-- | Surrounds all windows with blank space, and adds the same amount of spacing
+-- around the edge of the screen, except when the window is the only visible
+-- window on the current workspace.
+smartSpacingWithEdge :: Int -> l a -> ModifiedLayout SmartSpacingWithEdge l a
+smartSpacingWithEdge p = ModifiedLayout (SmartSpacingWithEdge p)
+
+data SmartSpacingWithEdge a = SmartSpacingWithEdge Int deriving (Show, Read)
+
+instance LayoutModifier SmartSpacingWithEdge a where
+
+ pureModifier _ _ _ [x] = ([x], Nothing)
+ pureModifier (SmartSpacingWithEdge p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
+
+ modifyLayout (SmartSpacingWithEdge p) w r
+ | maybe False (\s -> null (up s) && null (down s)) (stack w) = runLayout w r
+ | otherwise = runLayout w (shrinkRect p r)
+
+ modifierDescription (SmartSpacingWithEdge p) = "SmartSpacingWithEdge " ++ show p