aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Spacing.hs
diff options
context:
space:
mode:
authorBrent Yorgey <byorgey@cis.upenn.edu>2009-05-14 23:55:52 +0200
committerBrent Yorgey <byorgey@cis.upenn.edu>2009-05-14 23:55:52 +0200
commit6420f7edf75f64cb050cb867809d62c4de7f41ff (patch)
treefcf18e631a081cff5149d1012d41adfa373719a3 /XMonad/Layout/Spacing.hs
parentb6822b813463a63d94d80d1ba34b448591a493a5 (diff)
downloadXMonadContrib-6420f7edf75f64cb050cb867809d62c4de7f41ff.tar.gz
XMonadContrib-6420f7edf75f64cb050cb867809d62c4de7f41ff.tar.xz
XMonadContrib-6420f7edf75f64cb050cb867809d62c4de7f41ff.zip
new layout module X.L.Spacing, put blank space around each window
darcs-hash:20090514215552-1e371-f1100b7112ae24d4607a44c289eb1a9ebe8c4554.gz
Diffstat (limited to 'XMonad/Layout/Spacing.hs')
-rw-r--r--XMonad/Layout/Spacing.hs54
1 files changed, 54 insertions, 0 deletions
diff --git a/XMonad/Layout/Spacing.hs b/XMonad/Layout/Spacing.hs
new file mode 100644
index 0000000..1ff2202
--- /dev/null
+++ b/XMonad/Layout/Spacing.hs
@@ -0,0 +1,54 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Spacing
+-- Copyright : (c) Brent Yorgey
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : <byorgey@gmail.com>
+-- Stability : unstable
+-- Portability : portable
+--
+-- Add a configurable amount of space around windows.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Spacing (
+ -- * Usage
+ -- $usage
+
+ spacing
+
+ ) where
+
+import Graphics.X11 (Rectangle(..))
+import Control.Arrow (second)
+
+import XMonad.Layout.LayoutModifier
+
+-- $usage
+-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
+--
+-- > import XMonad.Layout.Spacing
+--
+-- and modifying your layoutHook as follows (for example):
+--
+-- > layoutHook = spacing 2 $ Tall 1 (3/100) (1/2)
+-- > -- put a 2px space around every window
+--
+
+-- | Surround all windows by a certain number of pixels of blank space.
+spacing :: Int -> l a -> ModifiedLayout Spacing l a
+spacing p = ModifiedLayout (Spacing p)
+
+data Spacing a = Spacing Int deriving (Show, Read)
+
+instance LayoutModifier Spacing a where
+
+ pureModifier (Spacing p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
+
+ modifierDescription (Spacing p) = "Spacing " ++ 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)
+ where fi n = fromIntegral n -- avoid the DMR