aboutsummaryrefslogtreecommitdiffstats
path: root/TilePrime.hs
diff options
context:
space:
mode:
authorEric Mertens <emertens@galois.com>2007-10-17 07:20:17 +0200
committerEric Mertens <emertens@galois.com>2007-10-17 07:20:17 +0200
commit5b8b0519ef33d62ca0069ebe7833d1452ec211e6 (patch)
treec0cf5ee3ea54b8f245573bad3544ffdf59d298b0 /TilePrime.hs
parent1ef20612dbe4146b36a360740cd3751cfab6ddb8 (diff)
downloadXMonadContrib-5b8b0519ef33d62ca0069ebe7833d1452ec211e6.tar.gz
XMonadContrib-5b8b0519ef33d62ca0069ebe7833d1452ec211e6.tar.xz
XMonadContrib-5b8b0519ef33d62ca0069ebe7833d1452ec211e6.zip
Initial import of TilePrime
This layout provides a standard tiling layout with support for resize hints and filling the gaps created by them. darcs-hash:20071017052017-b49f3-b41e5074afec8268ec9c41d77a04bb1cb3ea8f79.gz
Diffstat (limited to 'TilePrime.hs')
-rw-r--r--TilePrime.hs80
1 files changed, 80 insertions, 0 deletions
diff --git a/TilePrime.hs b/TilePrime.hs
new file mode 100644
index 0000000..08b3cca
--- /dev/null
+++ b/TilePrime.hs
@@ -0,0 +1,80 @@
+-- --------------------------------------------------------------------------
+-- -- |
+-- -- Module : TilePrime.hs
+-- -- Copyright : (c) Eric Mertens 2007
+-- -- License : BSD3-style (see LICENSE)
+-- --
+-- -- Maintainer : emertens@gmail.com
+-- -- Stability : unstable
+-- -- Portability : not portable
+-- --
+-- -- TilePrime. Tile windows filling gaps created by resize hints
+-- --
+-- -----------------------------------------------------------------------------
+--
+
+module XMonadContrib.TilePrime (TilePrime(TilePrime)) where
+
+import Control.Monad (mplus)
+import Data.List (genericLength)
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras (getWMNormalHints)
+import Operations
+import XMonad hiding (trace)
+import qualified StackSet as W
+import {-#SOURCE#-} Config (borderWidth)
+
+data TilePrime a = TilePrime
+ { nmaster :: Int
+ , delta, frac :: Rational
+ , flipped :: Bool
+ } deriving (Show, Read)
+
+instance LayoutClass TilePrime Window where
+ description _ = "TilePrime"
+
+ pureMessage c m = fmap resize (fromMessage m) `mplus`
+ fmap incmastern (fromMessage m)
+ where
+ resize Shrink = c { frac = max 0 $ frac c - delta c }
+ resize Expand = c { frac = min 1 $ frac c + delta c }
+ incmastern (IncMasterN d) = c { nmaster = max 0 $ nmaster c + d }
+
+ doLayout c rect s = do
+ let flp = flipped c
+ let xs = W.integrate s
+ hints <- withDisplay $ \ disp -> io (mapM (getWMNormalHints disp) xs)
+ let xs' = zip xs hints
+ (leftRect, rightRect)
+ | flp = splitVerticallyBy (frac c) rect
+ | otherwise = splitHorizontallyBy (frac c) rect
+ masters = fillWindows flp leftRect (take (nmaster c) xs')
+ slaves = fillWindows flp rightRect (drop (nmaster c) xs')
+ return (masters ++ slaves, Nothing)
+
+ where
+
+ fillWindows _ _ [] = []
+ fillWindows flp r ((x,hint):xs) = (x,r') : fillWindows flp rest xs
+ where
+ n = 1 + genericLength xs :: Rational
+
+ (alloca, _) | flp = splitHorizontallyBy (recip n) r
+ | otherwise = splitVerticallyBy (recip n) r
+
+ (w,h) = applySizeHints hint `underBorders` (rect_width alloca, rect_height alloca)
+
+ r' = r { rect_width = w, rect_height = h }
+
+ rest | flp = r { rect_x = rect_x r + toEnum (fromEnum w)
+ , rect_width = rect_width r - w }
+ | otherwise = r { rect_y = rect_y r + toEnum (fromEnum h)
+ , rect_height = rect_height r - h }
+
+-- | Transform a function on dimensions into one without regard for borders
+underBorders :: (D -> D) -> D -> D
+underBorders f = adjBorders 1 . f . adjBorders (-1)
+
+-- | Modify dimensions by a multiple of the current borders
+adjBorders :: Dimension -> D -> D
+adjBorders mult (w,h) = (w+2*mult*borderWidth, h+2*mult*borderWidth)