mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-15 04:05:53 -07:00
Make Combo build on GHC 6.8
This commit is contained in:
@@ -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
|
-- %import XMonad.Layout.Combo
|
||||||
-- %layout , combineTwo (TwoPane 0.03 0.5) (tabbed shrinkText defaultTConf) (tabbed shrinkText defaultTConf)
|
-- %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)
|
deriving (Read, Show)
|
||||||
|
|
||||||
combineTwo :: (Read a, Eq a, LayoutClass super (), LayoutClass l1 a, LayoutClass l2 a) =>
|
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 [] []
|
combineTwo = C2 [] []
|
||||||
|
|
||||||
instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Eq a, Typeable a)
|
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)
|
doLayout (C2 f w2 super l1 l2) rinput s = arrange (integrate s)
|
||||||
where arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage Hide)
|
where arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage Hide)
|
||||||
l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage Hide)
|
l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage Hide)
|
||||||
|
@@ -37,11 +37,11 @@ infixr 6 <||>, <//>, <-||>, <-//>, <||->, <//->, <|>, <-|>, <|->, </>, <-/>, </-
|
|||||||
|
|
||||||
(<||>), (<//>), (<-||>), (<-//>), (<||->), (<//->)
|
(<||>), (<//>), (<-||>), (<-//>), (<||->), (<//->)
|
||||||
:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) =>
|
:: (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)
|
(<|>), (<-|>), (<|->) :: (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)
|
(</>), (<-/>), (</->) :: (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.5)
|
||||||
(<-||>) = combineTwo (dragPane Vertical 0.1 0.2)
|
(<-||>) = combineTwo (dragPane Vertical 0.1 0.2)
|
||||||
|
Reference in New Issue
Block a user