aboutsummaryrefslogtreecommitdiffstats
path: root/Spiral.hs
diff options
context:
space:
mode:
authorbobstopper <bobstopper@bobturf.org>2007-07-21 02:23:07 +0200
committerbobstopper <bobstopper@bobturf.org>2007-07-21 02:23:07 +0200
commit5e0331117db3430beafafabe76f7a96f31ef2bf5 (patch)
treeb7fdd9c734659c84f7476a49671b135bf71fca72 /Spiral.hs
parent4fb5da0b504697a1f3eccc9e5ef8fdaf952f7ed9 (diff)
downloadXMonadContrib-5e0331117db3430beafafabe76f7a96f31ef2bf5.tar.gz
XMonadContrib-5e0331117db3430beafafabe76f7a96f31ef2bf5.tar.xz
XMonadContrib-5e0331117db3430beafafabe76f7a96f31ef2bf5.zip
Made the direction of spiral in Spiral.hs optionally configurable
darcs-hash:20070721002307-ee4f8-0d4e5abc504a5933c0840946a78cae1e768c1e23.gz
Diffstat (limited to 'Spiral.hs')
-rw-r--r--Spiral.hs19
1 files changed, 14 insertions, 5 deletions
diff --git a/Spiral.hs b/Spiral.hs
index 3d0ea1e..0e88b81 100644
--- a/Spiral.hs
+++ b/Spiral.hs
@@ -16,6 +16,9 @@ module XMonadContrib.Spiral (
-- * Usage
-- $usage
spiral
+ , spiralWithDir
+ , Rotation (..)
+ , Direction (..)
) where
import Graphics.X11.Xlib
@@ -43,7 +46,8 @@ mkRatios :: [Integer] -> [Rational]
mkRatios (x1:x2:xs) = (x1 % x2) : mkRatios (x2:xs)
mkRatios _ = []
-data Direction = East | South | West | North deriving (Enum)
+data Rotation = CW | CCW
+data Direction = East | South | West | North deriving (Eq, Enum)
blend :: Rational -> [Rational] -> [Rational]
blend scale ratios = zipWith (+) ratios scaleFactors
@@ -53,13 +57,18 @@ blend scale ratios = zipWith (+) ratios scaleFactors
scaleFactors = map (* step) . reverse . take len $ [0..]
spiral :: Rational -> Layout a
-spiral scale = Layout { doLayout = l2lModDo fibLayout,
- modifyLayout = \m -> return $ fmap resize $ fromMessage m }
+spiral = spiralWithDir East CW
+
+spiralWithDir :: Direction -> Rotation -> Rational -> Layout a
+spiralWithDir dir rot scale = Layout { doLayout = l2lModDo fibLayout,
+ modifyLayout = \m -> return $ fmap resize $ fromMessage m }
where
fibLayout sc ws = zip ws rects
where ratios = blend scale . reverse . take (length ws - 1) . mkRatios $ tail fibs
- rects = divideRects (zip ratios (cycle [East .. North])) sc
-
+ rects = divideRects (zip ratios dirs) sc
+ dirs = dropWhile (/= dir) $ case rot of
+ CW -> cycle [East .. North]
+ CCW -> cycle [North, West, South, East]
resize Expand = spiral $ (21 % 20) * scale
resize Shrink = spiral $ (20 % 21) * scale