From e0afe7f27200f1e5b2333bb99226e3345fdd63a4 Mon Sep 17 00:00:00 2001 From: Don Stewart Date: Sun, 10 Jun 2007 08:27:57 +0200 Subject: add DynamicLog.hs darcs-hash:20070610062757-9c5c1-daf166ca9232256e70963800bd34444d7d05d3e7.gz --- DynamicLog.hs | 49 +++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 49 insertions(+) create mode 100644 DynamicLog.hs (limited to 'DynamicLog.hs') diff --git a/DynamicLog.hs b/DynamicLog.hs new file mode 100644 index 0000000..48e4fff --- /dev/null +++ b/DynamicLog.hs @@ -0,0 +1,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 = "" -- cgit v1.2.3