aboutsummaryrefslogtreecommitdiffstats
path: root/DynamicLog.hs
diff options
context:
space:
mode:
authorJason Creighton <jcreigh@gmail.com>2007-06-11 07:18:10 +0200
committerJason Creighton <jcreigh@gmail.com>2007-06-11 07:18:10 +0200
commitd14325cc7cae512e7c20c95e7643cb72df2115ce (patch)
tree222eabc0a35d1e2aa90e69475a8bc8bcc4f11256 /DynamicLog.hs
parente6eb5e25a70b6be61f489d273ba58b144cd13f31 (diff)
downloadXMonadContrib-d14325cc7cae512e7c20c95e7643cb72df2115ce.tar.gz
XMonadContrib-d14325cc7cae512e7c20c95e7643cb72df2115ce.tar.xz
XMonadContrib-d14325cc7cae512e7c20c95e7643cb72df2115ce.zip
added dynamicLogXinerama, a workspace logger that's nicer for Xinerama
darcs-hash:20070611051810-b9aa7-1a6d385dc25cf8ef8005fd1e70ef9d2e0dc6e256.gz
Diffstat (limited to 'DynamicLog.hs')
-rw-r--r--DynamicLog.hs30
1 files changed, 25 insertions, 5 deletions
diff --git a/DynamicLog.hs b/DynamicLog.hs
index cc49c34..a137454 100644
--- a/DynamicLog.hs
+++ b/DynamicLog.hs
@@ -14,7 +14,7 @@
--
-- Don Stewart
-module XMonadContrib.DynamicLog where
+module XMonadContrib.DynamicLog (dynamicLog, dynamicLogXinerama) where
--
-- Useful imports
@@ -38,14 +38,34 @@ import qualified StackSet as S
dynamicLog :: X ()
dynamicLog = withWindowSet $ io . putStrLn . ppr
where
- ppr s = concatMap fmt $ sortBy tags
+ ppr s = concatMap fmt $ sortBy (compare `on` S.tag)
(map S.workspace (S.current s : S.visible s) ++ S.hidden s)
- where tags a b = S.tag a `compare` S.tag b
- this = S.tag (S.workspace (S.current s))
- pprTag = show . (+(1::Int)) . fromIntegral . S.tag
+ where this = S.tag (S.workspace (S.current s))
visibles = map (S.tag . S.workspace) (S.visible s)
fmt w | S.tag w == this = "[" ++ pprTag w ++ "]"
| S.tag w `elem` visibles = "<" ++ pprTag w ++ ">"
| S.stack w /= S.Empty = " " ++ pprTag w ++ " "
| otherwise = ""
+
+--
+-- Workspace logger with a format designed for Xinerama:
+--
+-- [1 9 3] 2 7
+--
+-- where 1, 9, and 3 are the workspaces on screens 1, 2 and 3, respectively,
+-- and 2 and 7 are non-visible, non-empty workspaces
+--
+dynamicLogXinerama :: X ()
+dynamicLogXinerama = withWindowSet $ io . putStrLn . ppr
+ where
+ ppr ws = "[" ++ unwords onscreen ++ "] " ++ unwords offscreen
+ where onscreen = map (pprTag . S.workspace) . sortBy (compare `on` S.screen) $ S.current ws : S.visible ws
+ offscreen = map pprTag . filter ((/= S.Empty) . S.stack) . sortBy (compare `on` S.tag) $ S.hidden ws
+
+-- util functions
+pprTag :: Integral i => S.Workspace i a -> String
+pprTag = show . (+(1::Int)) . fromIntegral . S.tag
+
+on :: (a -> a -> c) -> (b -> a) -> b -> b -> c
+on f g a b = (g a) `f` (g b)