aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/LayoutCombinators.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-31 07:39:29 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-31 07:39:29 +0100
commitb1eb3fcd01b0b6dd1042d58c54f0901d658efeeb (patch)
tree0b02530a09d81661f6253c766dbfccdbac1fd5b7 /XMonad/Layout/LayoutCombinators.hs
parent25a48e25941bc5064e391b44ce373d0561010e80 (diff)
downloadXMonadContrib-b1eb3fcd01b0b6dd1042d58c54f0901d658efeeb.tar.gz
XMonadContrib-b1eb3fcd01b0b6dd1042d58c54f0901d658efeeb.tar.xz
XMonadContrib-b1eb3fcd01b0b6dd1042d58c54f0901d658efeeb.zip
Remove LayoutCombinator class and revert PerWorkspace to its Maybe Bool state
As I said in order to have a CombinedLayout type instace of LayoutClass and a class for easily writing pure and impure combinators to be feeded to the CombinedLayout together with the layouts to be conbined, there's seems to be the need to change the type of the LayoutClass.description method from l a -> String to l a -> X String. Without that "ugly" change - loosing the purity of the description (please note the *every* methods of that class unless description operates in the X monad) - I'm plainly unable to write something really useful and maintainable. If someone can point me in the right direction I would really really appreciate. Since, in the meantime, PerWorkspace, which has its users, is broken and I broke it, I'm reverting it to it supposedly more beautiful PerWorkspac [WorkspaceId] (Maybe Bool) (l1 a) (l2 a) type. darcs-hash:20080131063929-32816-8e37919b38c70675a90e492f0c29674061ba3968.gz
Diffstat (limited to 'XMonad/Layout/LayoutCombinators.hs')
-rw-r--r--XMonad/Layout/LayoutCombinators.hs67
1 files changed, 1 insertions, 66 deletions
diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index d21af6d..67c09b0 100644
--- a/XMonad/Layout/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -41,12 +41,9 @@ module XMonad.Layout.LayoutCombinators
-- $nc
, (|||)
, JumpToLayout(JumpToLayout)
- , LayoutCombinator (..)
- , CombinedLayout (..)
- , ComboChooser (..)
) where
-import Data.Maybe ( fromMaybe, isJust, isNothing )
+import Data.Maybe ( isJust, isNothing )
import XMonad hiding ((|||))
import XMonad.Layout.Combo
@@ -220,65 +217,3 @@ passOnM m (NewSelect False lt lf) = do mlf' <- handleMessage lf m
when' :: Monad m => (a -> Bool) -> m a -> m a -> m a
when' f a b = do a1 <- a; if f a1 then b else return a1
-
-
-data ComboChooser = DoFirst | DoSecond | DoBoth deriving ( Eq, Show )
-
-class (Read (lc a), Show (lc a)) => LayoutCombinator lc a where
- chooser :: lc a -> X ComboChooser
- chooser lc = return $ pureChooser lc
- pureChooser :: lc a -> ComboChooser
- pureChooser _ = DoFirst
- combineResult :: lc a -> [(a,Rectangle)] -> [(a,Rectangle)] -> [(a,Rectangle)]
- combineResult _ wrs1 wrs2 = wrs1 ++ wrs2
- comboHandleMess :: (LayoutClass l1 a, LayoutClass l2 a) => lc a -> l1 a -> l2 a -> SomeMessage -> X (lc a)
- comboHandleMess lc l1 l2 m = return $ pureComboHandleMess lc l1 l2 m
- pureComboHandleMess :: (LayoutClass l1 a, LayoutClass l2 a) => lc a -> l1 a -> l2 a -> SomeMessage -> lc a
- pureComboHandleMess lc _ _ _ = lc
- sendToOther :: (LayoutClass l a) => lc a -> l a -> SomeMessage
- sendToOther _ _ = SomeMessage Hide
- comboDescription :: lc a -> String
- comboDescription _ = "Combine"
- combineDescription :: (LayoutClass l1 a, LayoutClass l2 a) => lc a -> l1 a -> l2 a -> String
- combineDescription lc l1 l2 = comboDescription lc <> description l1 <> description l2
- where "" <> x = x
- x <> y = x ++ " " ++ y
-
-data CombinedLayout lc l1 l2 a = CombinedLayout (lc a) (l1 a) (l2 a) deriving ( Show, Read )
-
-instance (LayoutClass l1 a, LayoutClass l2 a, LayoutCombinator lc a) => LayoutClass (CombinedLayout lc l1 l2) a where
- doLayout (CombinedLayout lc l1 l2) r s = do
- choose <- chooser lc
- case choose of
- DoSecond -> do (wrs, nl2) <- doLayout l2 r s
- return (wrs, Just $ CombinedLayout lc l1 (fromMaybe l2 nl2))
- DoBoth -> do (wrs1, nl1) <- doLayout l1 r s
- (wrs2, nl2) <- doLayout l2 r s
- return (combineResult lc wrs1 wrs2 , Just $ CombinedLayout lc (fromMaybe l1 nl1) (fromMaybe l2 nl2))
- _ -> do (wrs, nl1) <- doLayout l1 r s
- return (wrs, Just $ CombinedLayout lc (fromMaybe l1 nl1) l2)
- emptyLayout (CombinedLayout lc l1 l2) r = do
- choose <- chooser lc
- case choose of
- DoSecond -> do (wrs, nl2) <- emptyLayout l2 r
- return (wrs, Just $ CombinedLayout lc l1 (fromMaybe l2 nl2))
- DoBoth -> do (wrs1, nl1) <- emptyLayout l1 r
- (wrs2, nl2) <- emptyLayout l2 r
- return (combineResult lc wrs1 wrs2 , Just $ CombinedLayout lc (fromMaybe l1 nl1) (fromMaybe l2 nl2))
- _ -> do (wrs, nl1) <- emptyLayout l1 r
- return (wrs, Just $ CombinedLayout lc (fromMaybe l1 nl1) l2)
- handleMessage (CombinedLayout lc l1 l2) m = do
- nc <- comboHandleMess lc l1 l2 m
- choose <- chooser nc
- case choose of
- DoFirst -> do nl1 <- handleMessage l1 m
- nl2 <- handleMessage l2 (sendToOther nc l2)
- return $ Just $ CombinedLayout nc (fromMaybe l1 nl1) (fromMaybe l2 nl2)
- DoSecond -> do nl1 <- handleMessage l1 (sendToOther nc l1)
- nl2 <- handleMessage l2 m
- return $ Just $ CombinedLayout nc (fromMaybe l1 nl1) (fromMaybe l2 nl2)
- DoBoth -> do nl1 <- handleMessage l1 m
- nl2 <- handleMessage l2 m
- return $ Just $ CombinedLayout nc (fromMaybe l1 nl1) (fromMaybe l2 nl2)
-
- description (CombinedLayout lc l1 l2) = combineDescription lc l1 l2