aboutsummaryrefslogtreecommitdiffstats
path: root/DynamicLog.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-10-29 02:55:56 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-10-29 02:55:56 +0100
commit63a56368edb95cad0f850cfb019b8f8306417088 (patch)
treedad0d7075c396f0a7a056fce730c8ebc77272114 /DynamicLog.hs
parent7fb8f730af58a83ed31e41ccb6b083c9f127e7fd (diff)
downloadXMonadContrib-63a56368edb95cad0f850cfb019b8f8306417088.tar.gz
XMonadContrib-63a56368edb95cad0f850cfb019b8f8306417088.tar.xz
XMonadContrib-63a56368edb95cad0f850cfb019b8f8306417088.zip
Factor out some of dzenPP's goodies
darcs-hash:20071029015556-a5988-b5eaed14a2972febeab20104e41592146b93bd75.gz
Diffstat (limited to 'DynamicLog.hs')
-rw-r--r--DynamicLog.hs61
1 files changed, 35 insertions, 26 deletions
diff --git a/DynamicLog.hs b/DynamicLog.hs
index 4208b8a..980da5e 100644
--- a/DynamicLog.hs
+++ b/DynamicLog.hs
@@ -29,8 +29,9 @@ module XMonadContrib.DynamicLog (
pprWindowSet,
pprWindowSetXinerama,
- PP(..), defaultPP, sjanssenPP,
- wrap, dzenColor, xmobarColor, shorten
+ PP(..), defaultPP, dzenPP, sjanssenPP,
+ wrap, pad, shorten,
+ xmobarColor, dzenColor, dzenEscape
) where
--
@@ -69,30 +70,6 @@ import XMonadContrib.NamedWindows
dynamicLog :: X ()
dynamicLog = dynamicLogWithPP defaultPP
--- | An example log hook that emulates dwm's status bar, using colour codes printed to dzen
--- Requires dzen. Workspaces, xinerama, layouts and the window title are handled.
---
-dynamicLogDzen :: X ()
-dynamicLogDzen = dynamicLogWithPP dzenPP
- where
- dzenPP = defaultPP { ppCurrent = dzenColor "white" "#2b4f98" . pad
- , ppVisible = dzenColor "black" "#999999" . pad
- , ppHidden = dzenColor "black" "#cccccc" . pad
- , ppHiddenNoWindows = const ""
- , ppWsSep = ""
- , ppSep = ""
- , ppLayout = dzenColor "black" "#cccccc" .
- (\ x -> case x of
- "TilePrime Horizontal" -> " TTT "
- "TilePrime Vertical" -> " []= "
- "Hinted Full" -> " [ ] "
- _ -> pad x
- )
- , ppTitle = ("^bg(#324c80) " ++) . escape
- }
- escape = concatMap (\x -> if x == '^' then "^^" else [x])
- pad = wrap " " " "
-
-- |
-- A log function that uses the 'PP' hooks to customize output.
dynamicLogWithPP :: PP -> X ()
@@ -110,6 +87,13 @@ dynamicLogWithPP pp = do
, ppTitle pp wt
]
+-- | An example log hook that emulates dwm's status bar, using colour codes printed to dzen
+-- Requires dzen. Workspaces, xinerama, layouts and the window title are handled.
+--
+dynamicLogDzen :: X ()
+dynamicLogDzen = dynamicLogWithPP dzenPP
+
+
pprWindowSet :: PP -> WindowSet -> String
pprWindowSet pp s = sepBy (ppWsSep pp) $ map fmt $ sortBy cmp
(map S.workspace (S.current s : S.visible s) ++ S.hidden s)
@@ -153,6 +137,9 @@ wrap :: String -> String -> String -> String
wrap _ _ "" = ""
wrap l r m = l ++ m ++ r
+pad :: String -> String
+pad = wrap " " " "
+
shorten :: Int -> String -> String
shorten n xs | length xs < n = xs
| otherwise = (take (n - length end) xs) ++ end
@@ -169,6 +156,10 @@ dzenColor fg bg = wrap (fg1++bg1) (fg2++bg2)
(bg1,bg2) | null bg = ("","")
| otherwise = ("^bg(" ++ bg ++ ")","^bg()")
+-- | Escape any dzen metacharaters.
+dzenEscape :: String -> String
+dzenEscape = concatMap (\x -> if x == '^' then "^^" else [x])
+
xmobarColor :: String -> String -> String -> String
xmobarColor fg bg = wrap t "</fc>"
where t = concat ["<fc=", fg, if null bg then "" else "," ++ bg, ">"]
@@ -194,6 +185,24 @@ defaultPP = PP { ppCurrent = wrap "[" "]"
, ppLayout = id
, ppOrder = id }
+-- | Settings to emulate dwm's statusbar, dzen only
+dzenPP :: PP
+dzenPP = defaultPP { ppCurrent = dzenColor "white" "#2b4f98" . pad
+ , ppVisible = dzenColor "black" "#999999" . pad
+ , ppHidden = dzenColor "black" "#cccccc" . pad
+ , ppHiddenNoWindows = const ""
+ , ppWsSep = ""
+ , ppSep = ""
+ , ppLayout = dzenColor "black" "#cccccc" .
+ (\ x -> case x of
+ "TilePrime Horizontal" -> " TTT "
+ "TilePrime Vertical" -> " []= "
+ "Hinted Full" -> " [ ] "
+ _ -> pad x
+ )
+ , ppTitle = ("^bg(#324c80) " ++) . dzenEscape
+ }
+
-- | The options that sjanssen likes to use, as an example. Note the use of
-- 'xmobarColor' and the record update on defaultPP
sjanssenPP :: PP