aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Accordion.hs4
-rw-r--r--Circle.hs4
-rw-r--r--Magnifier.hs4
-rw-r--r--Square.hs2
4 files changed, 7 insertions, 7 deletions
diff --git a/Accordion.hs b/Accordion.hs
index 6d5369f..0b47c70 100644
--- a/Accordion.hs
+++ b/Accordion.hs
@@ -27,11 +27,11 @@ import Data.Ratio
-- > import XMonadContrib.Accordion
-- > defaultLayouts = [ accordion ]
-accordion :: Layout Window
+accordion :: Eq a => Layout a
accordion = Layout { doLayout = accordionLayout
, modifyLayout = const $ return Nothing }
-accordionLayout :: Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
+accordionLayout :: Eq a => Rectangle -> W.Stack a -> X [(a, Rectangle)]
accordionLayout sc ws = return $ (zip ups tops) ++
[(W.focus ws, mainPane)] ++
(zip dns bottoms)
diff --git a/Circle.hs b/Circle.hs
index e8d4a86..32f8b34 100644
--- a/Circle.hs
+++ b/Circle.hs
@@ -27,11 +27,11 @@ import StackSet (integrate)
--
-- > import XMonadContrib.Circle
-circle :: Layout Window
+circle :: Layout a
circle = Layout { doLayout = \r -> circleLayout r . integrate,
modifyLayout = return . const Nothing }
-circleLayout :: Rectangle -> [Window] -> X [(Window, Rectangle)]
+circleLayout :: Rectangle -> [a] -> X [(a, Rectangle)]
circleLayout _ [] = return []
circleLayout r (w:ws) = return $ (w, center r) : (zip ws sats)
where sats = map (satellite r) $ take (length ws) [0, pi * 2 / fromIntegral (length ws) ..]
diff --git a/Magnifier.hs b/Magnifier.hs
index 7f27dfb..cfe4c12 100644
--- a/Magnifier.hs
+++ b/Magnifier.hs
@@ -30,11 +30,11 @@ import StackSet
-- > import XMonadContrib.Magnifier
-- > defaultLayouts = [ magnifier tiled , magnifier $ mirror tiled ]
-magnifier :: Layout Window -> Layout Window
+magnifier :: Eq a => Layout a -> Layout a
magnifier l = l { doLayout = \r s -> applyMagnifier r s `fmap` doLayout l r s
, modifyLayout = \x -> fmap magnifier `fmap` modifyLayout l x }
-applyMagnifier :: Rectangle -> Stack Window -> [(Window, Rectangle)] -> [(Window, Rectangle)]
+applyMagnifier :: Eq a => Rectangle -> Stack a -> [(a, Rectangle)] -> [(a, Rectangle)]
applyMagnifier r s | null (up s) = id -- don't change the master window
| otherwise = map $ \(w,wr) -> if w == focus s then (w, shrink r $ magnify wr) else (w, wr)
diff --git a/Square.hs b/Square.hs
index 3564d62..4250410 100644
--- a/Square.hs
+++ b/Square.hs
@@ -40,7 +40,7 @@ import StackSet ( integrate )
-- > (mirror $ twoPane 0.03 0.85),1)] (twoPane 0.03 0.5) )
-square :: Layout Window
+square :: Layout a
square = Layout { doLayout = \r s -> arrange r (integrate s), modifyLayout = message }
where
arrange rect ws@(_:_) = do