aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks
diff options
context:
space:
mode:
authorwirtwolff <wirtwolff@gmail.com>2009-03-14 05:15:17 +0100
committerwirtwolff <wirtwolff@gmail.com>2009-03-14 05:15:17 +0100
commit968421004fe65227f0fd608494120c32eccd8cff (patch)
tree6ef05e68fa619d1b1f7f830a3371fcfd41756a3e /XMonad/Hooks
parent49f103cfdf558e469774b0a5e668823fdf11a91c (diff)
downloadXMonadContrib-968421004fe65227f0fd608494120c32eccd8cff.tar.gz
XMonadContrib-968421004fe65227f0fd608494120c32eccd8cff.tar.xz
XMonadContrib-968421004fe65227f0fd608494120c32eccd8cff.zip
H.DynamicLog: revised dzenStrip and xmobarStrip functions
Ignore-this: 9897c60b8dfc59344939b7aebc370953 Reconcile darcswatch patch with pushed version of dzenStrip. darcs-hash:20090314041517-d17f0-85d43c2bc0bddf3a6322c8ec195095117840e372.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r--XMonad/Hooks/DynamicLog.hs40
1 files changed, 30 insertions, 10 deletions
diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs
index b4bbe48..51fb70b 100644
--- a/XMonad/Hooks/DynamicLog.hs
+++ b/XMonad/Hooks/DynamicLog.hs
@@ -39,7 +39,8 @@ module XMonad.Hooks.DynamicLog (
-- * Formatting utilities
wrap, pad, shorten,
- xmobarColor, dzenColor, dzenEscape, dzenStrip,
+ xmobarColor, xmobarStrip,
+ dzenColor, dzenEscape, dzenStrip,
-- * Internal formatting functions
pprWindowSet,
@@ -332,16 +333,19 @@ dzenColor fg bg = wrap (fg1++bg1) (fg2++bg2)
dzenEscape :: String -> String
dzenEscape = concatMap (\x -> if x == '^' then "^^" else [x])
--- | Strip dzen formatting (used in ppUrgent)
+-- | Strip dzen formatting or commands. Useful to remove ppHidden
+-- formatting in ppUrgent field. For example:
+--
+-- > , ppHidden = dzenColor "gray20" "" . wrap "(" ")"
+-- > , ppUrgent = dzenColor "dark orange" "" . dzenStrip
dzenStrip :: String -> String
dzenStrip = strip [] where
- strip keep [] = keep
- strip keep ('^':'^':x) = strip (keep ++ "^") x
- strip keep ('^':x) = strip keep (drop 1 . dropWhile (')' /=) $ x)
- strip keep x = let (good,x') = span ('^' /=) x
- in strip (keep ++ good) x'
-
-
+ strip keep x
+ | null x = keep
+ | "^^" `isPrefixOf` x = strip (keep ++ "^") (drop 2 x)
+ | '^' == head x = strip keep (drop 1 . dropWhile (/= ')') $ x)
+ | otherwise = let (good,x') = span (/= '^') x
+ in strip (keep ++ good) x'
-- | Use xmobar escape codes to output a string with given foreground
-- and background colors.
@@ -354,6 +358,21 @@ xmobarColor fg bg = wrap t "</fc>"
-- ??? add an xmobarEscape function?
+-- | Strip xmobar markup. Useful to remove ppHidden color from ppUrgent
+-- field. For example:
+--
+-- > , ppHidden = xmobarColor "gray20" "" . wrap "<" ">"
+-- > , ppUrgent = xmobarColor "dark orange" "" . xmobarStrip
+xmobarStrip :: String -> String
+xmobarStrip = strip [] where
+ strip keep x
+ | null x = keep
+ | "<fc=" `isPrefixOf` x = strip keep (drop 1 . dropWhile (/= '>') $ x)
+ | "</fc>" `isPrefixOf` x = strip keep (drop 5 x)
+ | '<' == head x = strip (keep ++ "<") (tail x)
+ | otherwise = let (good,x') = span (/= '<') x
+ in strip (keep ++ good) x'
+
-- | The 'PP' type allows the user to customize the formatting of
-- status information.
data PP = PP { ppCurrent :: WorkspaceId -> String
@@ -426,7 +445,8 @@ defaultPP = PP { ppCurrent = wrap "[" "]"
, ppExtras = []
}
--- | Settings to emulate dwm's statusbar, dzen only.
+-- | Settings to emulate dwm's statusbar, dzen only. Uses dzenStrip in
+-- ppUrgent.
dzenPP :: PP
dzenPP = defaultPP { ppCurrent = dzenColor "white" "#2b4f98" . pad
, ppVisible = dzenColor "black" "#999999" . pad