blob: 48e4fffc05c08c25de70f44f638a51f634090ef4 (
plain) (
blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
|
--
-- DynamicLog
--
-- Log events in:
--
-- 1 2 [3] 4 8
--
-- format. suitable to pipe into dzen.
--
-- To use, set:
--
-- import XMonadContrib.DynamicLog
-- logHook = dynamicLog
--
-- Don Stewart
module XMonadContrib.DynamicLog where
--
-- Useful imports
--
import XMonad
import Data.List
import qualified StackSet as S
--
-- Perform an arbitrary action on each state change.
-- Examples include:
-- * do nothing
-- * log the state to stdout
--
-- An example logger, print a status bar output to dzen, in the form:
--
-- 1 2 [3] 4 7
--
dynamicLog :: X ()
dynamicLog = withWindowSet $ io . putStrLn . ppr
where
ppr s = concatMap fmt $ sortBy tags
(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
fmt w | S.tag w == this = "[" ++ pprTag w ++ "]"
| S.stack w /= S.Empty = " " ++ pprTag w ++ " "
| otherwise = ""
|