From 1977f3c4a6c88b1cc764d673db64b6da914eca88 Mon Sep 17 00:00:00 2001 From: "l.mai" Date: Fri, 5 Oct 2007 03:34:12 +0200 Subject: import Grid.hs into repository darcs-hash:20071005013412-42ea9-939a6c25ff07f732316c470040b9869d52b07534.gz --- Grid.hs | 48 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 48 insertions(+) create mode 100644 Grid.hs diff --git a/Grid.hs b/Grid.hs new file mode 100644 index 0000000..e4dcd11 --- /dev/null +++ b/Grid.hs @@ -0,0 +1,48 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonadContrib.Grid +-- Copyright : (c) Lukas Mai +-- License : BSD-style (see LICENSE) +-- +-- Maintainer : +-- Stability : unstable +-- Portability : unportable +-- +-- +----------------------------------------------------------------------------- + +module XMonadContrib.Grid ( + Grid(..) +) where + +import XMonad +import StackSet +import Graphics.X11.Xlib.Types + +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] -- cgit v1.2.3