From 6420f7edf75f64cb050cb867809d62c4de7f41ff Mon Sep 17 00:00:00 2001 From: Brent Yorgey Date: Thu, 14 May 2009 23:55:52 +0200 Subject: new layout module X.L.Spacing, put blank space around each window darcs-hash:20090514215552-1e371-f1100b7112ae24d4607a44c289eb1a9ebe8c4554.gz --- XMonad/Layout/Spacing.hs | 54 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 54 insertions(+) create mode 100644 XMonad/Layout/Spacing.hs (limited to 'XMonad/Layout/Spacing.hs') 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 : +-- 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 -- cgit v1.2.3