Fix type signatures.

Think this fixes the rest of the errors caused by the Layout change.
This commit is contained in:
joachim.fasting 2007-06-19 22:03:23 +00:00
parent 02f70419eb
commit 88d77b244f
14 changed files with 16 additions and 16 deletions

View File

@ -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 }

View File

@ -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 }

View File

@ -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'

View File

@ -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

View File

@ -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 }

View File

@ -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

View File

@ -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 }

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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)]

View File

@ -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

View File

@ -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)