diff options
-rw-r--r-- | Spiral.hs | 31 |
1 files changed, 25 insertions, 6 deletions
@@ -1,4 +1,4 @@ -module XMonadContrib.Spiral (spiral) where +module XMonadContrib.Spiral (spiral, fibSpiral) where import Graphics.X11.Xlib import Operations @@ -16,7 +16,7 @@ import XMonad -- spiral (1000 % 1618) ] -- spiral :: Rational -> Layout -spiral rat = Layout { doLayout = \sc ws -> return $ zip ws (divideRects rat (length ws) East $ sc), +spiral rat = Layout { doLayout = \sc ws -> return $ zip ws (divideRects (repeat rat) (length ws) East $ sc), modifyLayout = \m -> fmap resize (fromMessage m)} where resize Expand = let newRat = ((numerator rat + 10) % (denominator rat)) @@ -26,6 +26,24 @@ spiral rat = Layout { doLayout = \sc ws -> return $ zip ws (divideRects rat (len normRat = if numerator newRat < 0 then rat else newRat in spiral normRat +fibs :: [Integer] +fibs = 1 : 1 : (zipWith (+) fibs (tail fibs)) + +fibRatios :: [Rational] +fibRatios = ratios fibs + where + ratios (x:y:rs) = (x % y) : ratios (y:rs) + ratios _ = [] + +fibSpiral :: Rational -> Layout +fibSpiral scale = Layout { doLayout = fibLayout, + modifyLayout = \m -> fmap resize (fromMessage m) } + where + fibLayout sc ws = return $ zip ws (divideRects (map (* scale) . reverse . take len $ fibRatios) len East sc) + where len = length ws + resize Expand = fibSpiral $ (11 % 10) * scale + resize Shrink = fibSpiral $ (10 % 11) * scale + data Direction = East | South | West | North nextDir :: Direction -> Direction @@ -34,10 +52,11 @@ 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) +divideRects :: [Rational] -> Int -> Direction -> Rectangle -> [Rectangle] +divideRects [] _ _ _ = [] +divideRects (r:rs) n dir rect | n <= 1 = [rect] + | otherwise = case divideRect r dir rect of + (r1, r2) -> r1 : (divideRects rs (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 |