aboutsummaryrefslogtreecommitdiffstats
path: root/DynamicLog.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@galois.com>2007-10-13 21:51:29 +0200
committerDon Stewart <dons@galois.com>2007-10-13 21:51:29 +0200
commit91d5d906ab4b3133fec5222c9d6970b25eefda58 (patch)
treee40adf3db5f1b43100f587d737dc3a4c96309cbc /DynamicLog.hs
parent8f0f934c1ea7ecd18c57e204bcd0f53ed8478db2 (diff)
downloadXMonadContrib-91d5d906ab4b3133fec5222c9d6970b25eefda58.tar.gz
XMonadContrib-91d5d906ab4b3133fec5222c9d6970b25eefda58.tar.xz
XMonadContrib-91d5d906ab4b3133fec5222c9d6970b25eefda58.zip
clean up DynamicLog.hs
darcs-hash:20071013195129-cba2c-0f7b450f25113577cd57ce3c10e830f44f1c2678.gz
Diffstat (limited to 'DynamicLog.hs')
-rw-r--r--DynamicLog.hs60
1 files changed, 44 insertions, 16 deletions
diff --git a/DynamicLog.hs b/DynamicLog.hs
index d2ad23b..698feb9 100644
--- a/DynamicLog.hs
+++ b/DynamicLog.hs
@@ -21,7 +21,13 @@
module XMonadContrib.DynamicLog (
-- * Usage
-- $usage
- dynamicLog, dynamicLogWithTitle, dynamicLogWithTitleColored, dynamicLogXinerama, pprWindowSet, pprWindowSetXinerama
+ dynamicLog,
+ dynamicLogWithTitle,
+ dynamicLogWithTitleColored,
+ dynamicLogXinerama,
+
+ pprWindowSet,
+ pprWindowSetXinerama
) where
--
@@ -36,6 +42,7 @@ import Data.Ord ( comparing )
import qualified StackSet as S
import Data.Monoid
import XMonadContrib.NamedWindows
+import Data.Char
-- $usage
--
@@ -68,37 +75,58 @@ import XMonadContrib.NamedWindows
-- * do nothing
-- * log the state to stdout
--
--- An example logger, print a status bar output to dzen, in the form:
+-- |
+-- An example log hook, print a status bar output to dzen, in the form:
+--
+-- > 1 2 [3] 4 7 : full
--
--- > 1 2 [3] 4 7
+-- That is, the currently populated workspaces, and the current
+-- workspace layout
--
-
dynamicLog :: X ()
dynamicLog = withWindowSet $ \ws -> do
- let desc = description . S.layout . S.workspace . S.current $ ws
- io . putStrLn $ "(" ++ desc ++ ") " ++ pprWindowSet ws
+ let ld = description . S.layout . S.workspace . S.current $ ws
+ wn = pprWindowSet ws
+ io . putStrLn $ concat [wn ," : " ,map toLower ld]
--- Appends title of currently focused window to log output
+-- | Appends title of currently focused window to log output, and the
+-- current layout mode, to the normal dynamic log format.
-- Arguments are: pre-title text and post-title text
+--
+-- The result is rendered in the form:
+--
+-- > 1 2 [3] 4 7 : full : urxvt
+--
dynamicLogWithTitle_ :: String -> String -> X ()
-dynamicLogWithTitle_ pre post= do ld <- withWindowSet $ return . description . S.layout . S.workspace . S.current -- layout description
- ws <- withWindowSet $ return . pprWindowSet -- workspace list
- wt <- withWindowSet $ maybe (return "") (fmap show . getName) . S.peek -- window title
- io . putStrLn $ "(" ++ ld ++ ") " ++ ws ++ " " ++ pre ++ wt ++ post
+dynamicLogWithTitle_ pre post= do
+ -- layout description
+ ld <- withWindowSet $ return . description . S.layout . S.workspace . S.current
+ -- workspace list
+ ws <- withWindowSet $ return . pprWindowSet
+ -- window title
+ wt <- withWindowSet $ maybe (return "") (fmap show . getName) . S.peek
+
+ io . putStrLn $ concat [ws ," : " ,map toLower ld
+ , case wt of
+ [] -> []
+ s -> " : " ++ pre ++ s ++ post
+ ]
dynamicLogWithTitle :: X ()
-dynamicLogWithTitle = dynamicLogWithTitle_ "<" ">"
+dynamicLogWithTitle = dynamicLogWithTitle_ "" ""
--- As dynamicLogWithTitle but with colored window title instead of angle brackets (works with dzen only)
+-- |
+-- As for dynamicLogWithTitle but with colored window title (for dzen use)
+--
dynamicLogWithTitleColored :: String -> X ()
dynamicLogWithTitleColored color = dynamicLogWithTitle_ ("^fg(" ++ color ++ ")") "^fg()"
pprWindowSet :: WindowSet -> String
pprWindowSet s = concatMap fmt $ sortBy cmp
(map S.workspace (S.current s : S.visible s) ++ S.hidden s)
- where f Nothing Nothing = EQ
- f (Just _) Nothing = LT
- f Nothing (Just _) = GT
+ where f Nothing Nothing = EQ
+ f (Just _) Nothing = LT
+ f Nothing (Just _) = GT
f (Just x) (Just y) = compare x y
wsIndex = flip elemIndex workspaces . S.tag