diff options
author | Spencer Janssen <sjanssen@cse.unl.edu> | 2007-11-06 03:11:26 +0100 |
---|---|---|
committer | Spencer Janssen <sjanssen@cse.unl.edu> | 2007-11-06 03:11:26 +0100 |
commit | a98fe45c43eba9c97c75671080d5e7bc751826d3 (patch) | |
tree | 32b295b29ebe845916e52959a16737e61d3a5485 /XMonad | |
parent | e52e66022b6447dacb9f1ebf5912afdbb9f64468 (diff) | |
download | XMonadContrib-a98fe45c43eba9c97c75671080d5e7bc751826d3.tar.gz XMonadContrib-a98fe45c43eba9c97c75671080d5e7bc751826d3.tar.xz XMonadContrib-a98fe45c43eba9c97c75671080d5e7bc751826d3.zip |
Make Combo build on GHC 6.8
darcs-hash:20071106021126-a5988-fae80b27ca3baaf00dbcaf103dcd9147fa7abbab.gz
Diffstat (limited to 'XMonad')
-rw-r--r-- | XMonad/Layout/Combo.hs | 9 | ||||
-rw-r--r-- | XMonad/Layout/LayoutCombinators.hs | 6 |
2 files changed, 8 insertions, 7 deletions
diff --git a/XMonad/Layout/Combo.hs b/XMonad/Layout/Combo.hs index aa9c016..9924be4 100644 --- a/XMonad/Layout/Combo.hs +++ b/XMonad/Layout/Combo.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} +{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, + UndecidableInstances, PatternGuards #-} ----------------------------------------------------------------------------- -- | @@ -63,15 +64,15 @@ import qualified XMonad.StackSet as W ( differentiate ) -- %import XMonad.Layout.Combo -- %layout , combineTwo (TwoPane 0.03 0.5) (tabbed shrinkText defaultTConf) (tabbed shrinkText defaultTConf) -data CombineTwo l l1 l2 a = C2 [a] [a] (l ()) (l1 a) (l2 a) +data CombineTwo l l1 l2 a = C2 [a] [a] l (l1 a) (l2 a) deriving (Read, Show) combineTwo :: (Read a, Eq a, LayoutClass super (), LayoutClass l1 a, LayoutClass l2 a) => - super () -> l1 a -> l2 a -> CombineTwo super l1 l2 a + super () -> l1 a -> l2 a -> CombineTwo (super ()) l1 l2 a combineTwo = C2 [] [] instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a) - => LayoutClass (CombineTwo l l1 l2) a where + => LayoutClass (CombineTwo (l ()) l1 l2) a where doLayout (C2 f w2 super l1 l2) rinput s = arrange (integrate s) where arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage Hide) l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage Hide) diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs index 7b3734d..f9b37fd 100644 --- a/XMonad/Layout/LayoutCombinators.hs +++ b/XMonad/Layout/LayoutCombinators.hs @@ -37,11 +37,11 @@ infixr 6 <||>, <//>, <-||>, <-//>, <||->, <//->, <|>, <-|>, <|->, </>, <-/>, </- (<||>), (<//>), (<-||>), (<-//>), (<||->), (<//->) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => - l1 a -> l2 a -> CombineTwo DragPane l1 l2 a + l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (<|>), (<-|>), (<|->) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) - => l1 a -> l2 a -> CombineTwo Tall l1 l2 a + => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (</>), (<-/>), (</->) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) - => l1 a -> l2 a -> CombineTwo (Mirror Tall) l1 l2 a + => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (<||>) = combineTwo (dragPane Vertical 0.1 0.5) (<-||>) = combineTwo (dragPane Vertical 0.1 0.2) |