aboutsummaryrefslogtreecommitdiffstats
path: root/Spiral.hs
diff options
context:
space:
mode:
authorjoe.thornber <joe.thornber@gmail.com>2007-05-22 08:25:37 +0200
committerjoe.thornber <joe.thornber@gmail.com>2007-05-22 08:25:37 +0200
commit95d875d8b180a38921e11b21ddb316efed55f665 (patch)
treec4c3e6f230752571332171716c633c88bf481b04 /Spiral.hs
parent9ae5945d2f5659210414608c270b423dbecbacdf (diff)
downloadXMonadContrib-95d875d8b180a38921e11b21ddb316efed55f665.tar.gz
XMonadContrib-95d875d8b180a38921e11b21ddb316efed55f665.tar.xz
XMonadContrib-95d875d8b180a38921e11b21ddb316efed55f665.zip
[SPIRAL] add spiral tiling layout
darcs-hash:20070522062537-db939-eb4cf54b320ba2211dec3bcbc7786e904eb5bc4d.gz
Diffstat (limited to 'Spiral.hs')
-rw-r--r--Spiral.hs58
1 files changed, 58 insertions, 0 deletions
diff --git a/Spiral.hs b/Spiral.hs
new file mode 100644
index 0000000..7df6eb5
--- /dev/null
+++ b/Spiral.hs
@@ -0,0 +1,58 @@
+module Spiral (spiral) where
+
+import Graphics.X11.Xlib
+import Operations
+import Data.Ratio
+import XMonad
+
+--
+-- Spiral layout
+--
+-- eg,
+-- defaultLayouts :: [Layout]
+-- defaultLayouts = [ full,
+-- tall defaultWindowsInMaster defaultDelta (1%2),
+-- wide defaultWindowsInMaster defaultDelta (1%2),
+-- spiral (1000 % 1618) ]
+--
+spiral :: Rational -> Layout
+spiral rat = Layout { doLayout = \sc ws -> return $ zip ws (divideRects rat (length ws) East $ sc),
+ modifyLayout = \m -> fmap resize (fromMessage m)}
+
+ where resize Expand = let newRat = ((numerator rat + 10) % (denominator rat))
+ normRat = if numerator newRat > denominator newRat then rat else newRat in
+ spiral normRat
+ resize Shrink = let newRat = ((numerator rat - 10) % (denominator rat))
+ normRat = if numerator newRat < 0 then rat else newRat in
+ spiral normRat
+
+data Direction = East | South | West | North
+
+nextDir :: Direction -> Direction
+nextDir East = South
+nextDir South = West
+nextDir West = North
+nextDir North = East
+
+divideRects :: Rational -> Int -> Direction -> Rectangle -> [Rectangle]
+divideRects r n dir rect | n <= 1 = [rect]
+ | otherwise = case divideRect r dir rect of
+ (r1, r2) -> r1 : (divideRects r (n - 1) (nextDir dir) r2)
+
+divideRect :: Rational -> Direction -> Rectangle -> (Rectangle, Rectangle)
+divideRect ratio East (Rectangle x y w h) = let (w1, w2) = chop ratio (fromIntegral w) in
+ (Rectangle x y (fromIntegral w1) h,
+ Rectangle (x + (fromIntegral w1)) y (fromIntegral w2) h)
+divideRect ratio South (Rectangle x y w h) = let (h1, h2) = chop ratio (fromIntegral h) in
+ (Rectangle x y w (fromIntegral h1),
+ Rectangle x (y + (fromIntegral h1)) w (fromIntegral h2))
+divideRect ratio West (Rectangle x y w h) = let (w1, w2) = chop (1 - ratio) (fromIntegral w) in
+ (Rectangle (x + (fromIntegral w1)) y (fromIntegral w2) h,
+ Rectangle x y (fromIntegral w1) h)
+divideRect ratio North (Rectangle x y w h) = let (h1, h2) = chop (1 - ratio) (fromIntegral h) in
+ (Rectangle x (y + (fromIntegral h1)) w (fromIntegral h2),
+ Rectangle x y w (fromIntegral h1))
+
+chop :: Rational -> Integer -> (Integer, Integer)
+chop rat n = let f = ((fromIntegral n) * (numerator rat)) `div` (denominator rat) in
+ (f, n - f)