aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorjoachim.fasting <joachim.fasting@gmail.com>2007-06-20 00:03:23 +0200
committerjoachim.fasting <joachim.fasting@gmail.com>2007-06-20 00:03:23 +0200
commit346cc3269ee31062fa7eb560f90c4059c6279962 (patch)
treed3fce63e93e074dbec7eaa5b261b0d65f8d0219e
parentb5826d369dabc893c9fa7bf1a97915c4c7f4967e (diff)
downloadXMonadContrib-346cc3269ee31062fa7eb560f90c4059c6279962.tar.gz
XMonadContrib-346cc3269ee31062fa7eb560f90c4059c6279962.tar.xz
XMonadContrib-346cc3269ee31062fa7eb560f90c4059c6279962.zip
Fix type signatures.
Think this fixes the rest of the errors caused by the Layout change. darcs-hash:20070619220323-ea16c-3274cd24d01bc932089ab88191ccda316ea93b01.gz
-rw-r--r--Accordion.hs2
-rw-r--r--Circle.hs2
-rw-r--r--Combo.hs4
-rw-r--r--HintedTile.hs2
-rw-r--r--LayoutHints.hs2
-rw-r--r--LayoutHooks.hs2
-rw-r--r--Magnifier.hs2
-rw-r--r--Mosaic.hs2
-rw-r--r--NoBorders.hs4
-rw-r--r--Spiral.hs2
-rw-r--r--Square.hs2
-rw-r--r--Tabbed.hs2
-rw-r--r--TwoPane.hs2
-rw-r--r--WorkspaceDir.hs2
14 files changed, 16 insertions, 16 deletions
diff --git a/Accordion.hs b/Accordion.hs
index 82a1853..6d5369f 100644
--- a/Accordion.hs
+++ b/Accordion.hs
@@ -27,7 +27,7 @@ import Data.Ratio
-- > import XMonadContrib.Accordion
-- > defaultLayouts = [ accordion ]
-accordion :: Layout
+accordion :: Layout Window
accordion = Layout { doLayout = accordionLayout
, modifyLayout = const $ return Nothing }
diff --git a/Circle.hs b/Circle.hs
index 133a730..e8d4a86 100644
--- a/Circle.hs
+++ b/Circle.hs
@@ -27,7 +27,7 @@ import StackSet (integrate)
--
-- > import XMonadContrib.Circle
-circle :: Layout
+circle :: Layout Window
circle = Layout { doLayout = \r -> circleLayout r . integrate,
modifyLayout = return . const Nothing }
diff --git a/Combo.hs b/Combo.hs
index bdefcb3..80375c2 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -34,7 +34,7 @@ import Operations ( UnDoLayout(UnDoLayout) )
--
-- to your defaultLayouts.
-combo :: [(Layout, Int)] -> Layout -> Layout
+combo :: [(Layout a, Int)] -> Layout a -> Layout a
combo origls super = Layout { doLayout = \r s -> arrange r (integrate s), modifyLayout = message }
where arrange _ [] = return []
arrange r [w] = return [(w,r)]
@@ -56,7 +56,7 @@ combo origls super = Layout { doLayout = \r s -> arrange r (integrate s), modify
Nothing -> return Nothing
Just super' -> return $ Just $ combo origls super'
-broadcastPrivate :: Message a => a -> [Layout] -> X [Layout]
+broadcastPrivate :: Message a => a -> [Layout b] -> X [Layout b]
broadcastPrivate a ol = mapM f ol
where f l = do ml' <- modifyLayout l (SomeMessage a) `catchX` return (Just l)
return $ maybe l id ml'
diff --git a/HintedTile.hs b/HintedTile.hs
index 6ec408e..3df8014 100644
--- a/HintedTile.hs
+++ b/HintedTile.hs
@@ -37,7 +37,7 @@ addBorder (w, h) = (w + 2 * borderWidth, h + 2 * borderWidth)
substractBorder (w, h) = (w - 2 * borderWidth, h - 2 * borderWidth)
-tall, wide :: Int -> Rational -> Rational -> Layout
+tall, wide :: Int -> Rational -> Rational -> Layout Window
wide = tile splitVertically divideHorizontally
tall = tile splitHorizontally divideVertically
diff --git a/LayoutHints.hs b/LayoutHints.hs
index 61aa6d8..ab23ebe 100644
--- a/LayoutHints.hs
+++ b/LayoutHints.hs
@@ -31,7 +31,7 @@ import XMonad hiding ( trace )
adjBorders :: Dimension -> D -> D
adjBorders mult (w,h) = (w+2*mult*borderWidth, h+2*mult*borderWidth)
-layoutHints :: Layout -> Layout
+layoutHints :: Layout Window -> Layout Window
layoutHints l = l { doLayout = \r x -> doLayout l r x >>= applyHints
, modifyLayout = \x -> fmap layoutHints `fmap` modifyLayout l x }
diff --git a/LayoutHooks.hs b/LayoutHooks.hs
index 2261107..9a4a95d 100644
--- a/LayoutHooks.hs
+++ b/LayoutHooks.hs
@@ -20,7 +20,7 @@ import Control.Monad.State ( modify )
import XMonad
import qualified StackSet as W
-install :: (SomeMessage -> X Bool) -> Layout -> Layout
+install :: (SomeMessage -> X Bool) -> Layout a -> Layout a
install hk lay = lay{ modifyLayout = mod' }
where
mod' msg = do reinst <- hk msg
diff --git a/Magnifier.hs b/Magnifier.hs
index 8334844..7f27dfb 100644
--- a/Magnifier.hs
+++ b/Magnifier.hs
@@ -30,7 +30,7 @@ import StackSet
-- > import XMonadContrib.Magnifier
-- > defaultLayouts = [ magnifier tiled , magnifier $ mirror tiled ]
-magnifier :: Layout -> Layout
+magnifier :: Layout Window -> Layout Window
magnifier l = l { doLayout = \r s -> applyMagnifier r s `fmap` doLayout l r s
, modifyLayout = \x -> fmap magnifier `fmap` modifyLayout l x }
diff --git a/Mosaic.hs b/Mosaic.hs
index d4e09b3..2879d21 100644
--- a/Mosaic.hs
+++ b/Mosaic.hs
@@ -90,7 +90,7 @@ defaultArea = 1
flexibility :: Double
flexibility = 0.1
-mosaic :: Double -> Double -> M.Map NamedWindow [WindowHint] -> Layout
+mosaic :: Double -> Double -> M.Map NamedWindow [WindowHint] -> Layout Window
mosaic delta tileFrac hints = full { doLayout = \r -> mosaicL tileFrac hints r . W.integrate, modifyLayout = return . mlayout }
where mlayout x = (m1 `fmap` fromMessage x) `mplus` (m2 `fmap` fromMessage x)
m1 Shrink = mosaic delta (tileFrac/(1+delta)) hints
diff --git a/NoBorders.hs b/NoBorders.hs
index e0862f8..5588b8b 100644
--- a/NoBorders.hs
+++ b/NoBorders.hs
@@ -37,10 +37,10 @@ import {-# SOURCE #-} Config (borderWidth)
--
-- > layouts = [ noBorders full, tall, ... ]
-noBorders :: Layout -> Layout
+noBorders :: Layout a -> Layout a
noBorders = withBorder 0
-withBorder :: Dimension -> Layout -> Layout
+withBorder :: Dimension -> Layout a -> Layout a
withBorder bd l = l { doLayout = \r x -> setborders bd >> doLayout l r x
, modifyLayout = ml }
where ml m | Just UnDoLayout == fromMessage m
diff --git a/Spiral.hs b/Spiral.hs
index ce115e5..bf3197b 100644
--- a/Spiral.hs
+++ b/Spiral.hs
@@ -51,7 +51,7 @@ blend scale ratios = zipWith (+) ratios scaleFactors
step = (scale - (1 % 1)) / (fromIntegral len)
scaleFactors = map (* step) . reverse . take len $ [0..]
-spiral :: Rational -> Layout
+spiral :: Rational -> Layout a
spiral scale = Layout { doLayout = \r -> fibLayout r . W.integrate,
modifyLayout = \m -> return $ fmap resize $ fromMessage m }
where
diff --git a/Square.hs b/Square.hs
index 3f9e29e..3564d62 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
+square :: Layout Window
square = Layout { doLayout = \r s -> arrange r (integrate s), modifyLayout = message }
where
arrange rect ws@(_:_) = do
diff --git a/Tabbed.hs b/Tabbed.hs
index d81ccbc..031f9c5 100644
--- a/Tabbed.hs
+++ b/Tabbed.hs
@@ -40,7 +40,7 @@ import XMonadContrib.NamedWindows
-- > , ... ]
-tabbed :: Shrinker -> Layout
+tabbed :: Shrinker -> Layout Window
tabbed shrinkT = Layout { doLayout = dolay shrinkT, modifyLayout = const (return Nothing) }
dolay :: Shrinker -> Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
diff --git a/TwoPane.hs b/TwoPane.hs
index f5c9c92..b4d5f41 100644
--- a/TwoPane.hs
+++ b/TwoPane.hs
@@ -34,7 +34,7 @@ import StackSet ( focus, up, down)
--
-- > twoPane defaultDelta (1%2)
-twoPane :: Rational -> Rational -> Layout
+twoPane :: Rational -> Rational -> Layout a
twoPane delta split = Layout { doLayout = \r s -> return $ arrange r s, modifyLayout = message }
where
arrange rect st = case reverse (up st) of
diff --git a/WorkspaceDir.hs b/WorkspaceDir.hs
index cd84263..dba4b35 100644
--- a/WorkspaceDir.hs
+++ b/WorkspaceDir.hs
@@ -47,7 +47,7 @@ import XMonadContrib.Dmenu ( dmenu, runProcessWithInput )
data Chdir = Chdir String deriving ( Typeable )
instance Message Chdir
-workspaceDir :: String -> Layout -> Layout
+workspaceDir :: String -> Layout a -> Layout a
workspaceDir wd l = l { doLayout = \r x -> scd wd >> doLayout l r x
, modifyLayout = ml }
where ml m | Just (Chdir wd') <- fromMessage m = return $ Just (workspaceDir wd' l)