aboutsummaryrefslogtreecommitdiffstats
path: root/Combo.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-10-15 15:28:39 +0200
committerDavid Roundy <droundy@darcs.net>2007-10-15 15:28:39 +0200
commitb2d9ce8ee33bc74b846c2aa5aaced33864c75a64 (patch)
treec8c74c72659957b03fc7919e51fbfed15dd4ee96 /Combo.hs
parent579209ead201cb5ad7d9ea775bc22f0858685618 (diff)
downloadXMonadContrib-b2d9ce8ee33bc74b846c2aa5aaced33864c75a64.tar.gz
XMonadContrib-b2d9ce8ee33bc74b846c2aa5aaced33864c75a64.tar.xz
XMonadContrib-b2d9ce8ee33bc74b846c2aa5aaced33864c75a64.zip
improvements in Combo.
darcs-hash:20071015132839-72aca-90f2480c63facfb2d0f24ce75bbcccbabe40bcf0.gz
Diffstat (limited to 'Combo.hs')
-rw-r--r--Combo.hs25
1 files changed, 15 insertions, 10 deletions
diff --git a/Combo.hs b/Combo.hs
index 70c67d1..558928b 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -24,7 +24,9 @@ import Control.Arrow ( first )
import Data.List ( delete )
import Data.Maybe ( isJust )
import XMonad
+import Operations ( LayoutMessages(ReleaseResources) )
import StackSet ( integrate, Stack(..) )
+import XMonadContrib.Invisible
import qualified StackSet as W ( differentiate )
-- $usage
@@ -51,16 +53,16 @@ import qualified StackSet as W ( differentiate )
combo :: (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int))
=> (l (Layout a, Int)) -> [(Layout a, Int)] -> Combo l a
-combo = Combo []
+combo = Combo (I [])
-data Combo l a = Combo [a] (l (Layout a, Int)) [(Layout a, Int)]
+data Combo l a = Combo (Invisible [] a) (l (Layout a, Int)) [(Layout a, Int)]
deriving (Show, Read)
-instance (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int))
+instance (Eq a, ReadableLayout a, LayoutClass l (Layout a, Int))
=> LayoutClass (Combo l) a where
- doLayout (Combo f super origls) rinput s = arrange (integrate s)
- where arrange [] = return ([], Just $ Combo [] super origls)
- arrange [w] = return ([(w,rinput)], Just $ Combo [w] super origls)
+ doLayout (Combo (I f) super origls) rinput s = arrange (integrate s)
+ where arrange [] = return ([], Just $ Combo (I []) super origls)
+ arrange [w] = return ([(w,rinput)], Just $ Combo (I [w]) super origls)
arrange origws =
do (lrs, msuper') <- runLayout super rinput (W.differentiate $ take (length origws) origls)
let super' = maybe super id msuper'
@@ -73,20 +75,23 @@ instance (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int))
let origls' = zipWith foo (out++repeat ([],Nothing)) origls
foo (_, Nothing) x = x
foo (_, Just l') (_, n) = (l', n)
- return (concat $ map fst out, Just $ Combo f' super' origls')
+ return (concat $ map fst out, Just $ Combo (I f') super' origls')
differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q)
differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z
, up = reverse $ takeWhile (/=z) xs
, down = tail $ dropWhile (/=z) xs }
| otherwise = differentiate zs xs
differentiate [] xs = W.differentiate xs
- handleMessage (Combo f super origls) m =
+ handleMessage (Combo (I f) super origls) m =
do mls <- broadcastPrivate m (map fst origls)
let mls' = (\x->zipWith first (map const x) origls) `fmap` mls
+ f' = case fromMessage m of
+ Just ReleaseResources -> []
+ _ -> f
msuper <- broadcastPrivate m [super]
case msuper of
- Just [super'] -> return $ Just $ Combo f super' $ maybe origls id mls'
- _ -> return $ Combo f super `fmap` mls'
+ Just [super'] -> return $ Just $ Combo (I f') super' $ maybe origls id mls'
+ _ -> return $ Combo (I f') super `fmap` mls'
broadcastPrivate :: LayoutClass l b => SomeMessage -> [l b] -> X (Maybe [l b])
broadcastPrivate a ol = do nml <- mapM f ol