aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Grid.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Layout/Grid.hs')
-rw-r--r--XMonad/Layout/Grid.hs65
1 files changed, 65 insertions, 0 deletions
diff --git a/XMonad/Layout/Grid.hs b/XMonad/Layout/Grid.hs
new file mode 100644
index 0000000..b10a8ac
--- /dev/null
+++ b/XMonad/Layout/Grid.hs
@@ -0,0 +1,65 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Grid
+-- Copyright : (c) Lukas Mai
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : <l.mai@web.de>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A simple layout that attempts to put all windows in a square grid.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Grid (
+ -- * Usage
+ -- $usage
+ Grid(..)
+) where
+
+import XMonad
+import XMonad.StackSet
+import Graphics.X11.Xlib.Types
+
+-- $usage
+-- Put the following in your Config.hs file:
+--
+-- > import XMonad.Layout.Grid
+-- > ...
+-- > layouts = [ ...
+-- > , Layout Grid
+-- > ]
+
+-- %import XMonad.Layout.Grid
+-- %layout , Layout Grid
+
+data Grid a = Grid deriving (Read, Show)
+
+instance LayoutClass Grid a where
+ pureLayout Grid r s = arrange r (integrate s)
+
+arrange :: Rectangle -> [a] -> [(a, Rectangle)]
+arrange (Rectangle rx ry rw rh) st = zip st rectangles
+ where
+ nwins = length st
+ ncols = ceiling . (sqrt :: Double -> Double) . fromIntegral $ nwins
+ mincs = nwins `div` ncols
+ extrs = nwins - ncols * mincs
+ chop :: Int -> Dimension -> [(Position, Dimension)]
+ chop n m = ((0, m - k * fromIntegral (pred n)) :) . map (flip (,) k) . tail . reverse . take n . tail . iterate (subtract k') $ m'
+ where
+ k :: Dimension
+ k = m `div` fromIntegral n
+ m' = fromIntegral m
+ k' :: Position
+ k' = fromIntegral k
+ xcoords = chop ncols rw
+ ycoords = chop mincs rh
+ ycoords' = chop (succ mincs) rh
+ (xbase, xext) = splitAt (ncols - extrs) xcoords
+ rectangles = combine ycoords xbase ++ combine ycoords' xext
+ where
+ combine ys xs = [Rectangle (rx + x) (ry + y) w h | (x, w) <- xs, (y, h) <- ys]