85 lines
3.5 KiB
Diff
85 lines
3.5 KiB
Diff
diff --git a/XMonad/Hooks/DynamicLog.hs b/XMonad/Hooks/DynamicLog.hs
|
|
index 0547c80..1d256c6 100644
|
|
--- a/XMonad/Hooks/DynamicLog.hs
|
|
+++ b/XMonad/Hooks/DynamicLog.hs
|
|
@@ -1,4 +1,4 @@
|
|
-{-# LANGUAGE FlexibleContexts #-}
|
|
+{-# LANGUAGE FlexibleContexts, PatternGuards #-}
|
|
|
|
-----------------------------------------------------------------------------
|
|
-- |
|
|
@@ -57,10 +57,10 @@ module XMonad.Hooks.DynamicLog (
|
|
-- Useful imports
|
|
|
|
import Codec.Binary.UTF8.String (encodeString)
|
|
-import Control.Monad (liftM2)
|
|
+import Control.Monad (liftM2, msum)
|
|
import Data.Char ( isSpace, ord )
|
|
-import Data.List (intersperse, isPrefixOf, sortBy)
|
|
-import Data.Maybe ( isJust, catMaybes )
|
|
+import Data.List (intersperse, stripPrefix, isPrefixOf, sortBy)
|
|
+import Data.Maybe ( isJust, catMaybes, mapMaybe )
|
|
import Data.Ord ( comparing )
|
|
import qualified Data.Map as M
|
|
import qualified XMonad.StackSet as S
|
|
@@ -279,7 +279,7 @@ dynamicLogString pp = do
|
|
return $ encodeString . sepBy (ppSep pp) . ppOrder pp $
|
|
[ ws
|
|
, ppLayout pp ld
|
|
- , ppTitle pp wt
|
|
+ , ppTitle pp $ ppTitleSanitize pp wt
|
|
]
|
|
++ catMaybes extras
|
|
|
|
@@ -396,14 +396,26 @@ xmobarColor fg bg = wrap t "</fc>"
|
|
|
|
-- | Strip xmobar markup.
|
|
xmobarStrip :: String -> String
|
|
-xmobarStrip = strip [] where
|
|
+xmobarStrip = xmobarStripTags ["fc","icon","action"] where
|
|
+
|
|
+xmobarStripTags :: [String] -- ^ tags
|
|
+ -> String -> String -- ^ with all <tag>...</tag> removed
|
|
+xmobarStripTags tags = strip [] where
|
|
+ strip keep [] = keep
|
|
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'
|
|
+ | rest: _ <- mapMaybe dropTag tags = strip keep rest
|
|
+
|
|
+
|
|
+ | '<':xs <- x = strip (keep ++ "<") xs
|
|
+ | (good,x') <- span (/= '<') x = strip (keep ++ good) x' -- this is n^2 bad... but titles have few tags
|
|
+ where dropTag :: String -> Maybe String
|
|
+ dropTag tag = msum [fmap dropTilClose (openTag tag `stripPrefix` x),
|
|
+ closeTag tag `stripPrefix` x]
|
|
+
|
|
+ dropTilClose, openTag, closeTag :: String -> String
|
|
+ dropTilClose = drop 1 . dropWhile (/= '>')
|
|
+ openTag str = "<" ++ str ++ "="
|
|
+ closeTag str = "</" ++ str ++ ">"
|
|
|
|
-- | The 'PP' type allows the user to customize the formatting of
|
|
-- status information.
|
|
@@ -427,6 +439,8 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
|
|
-- ^ separator to use between workspace tags
|
|
, ppTitle :: String -> String
|
|
-- ^ window title format
|
|
+ , ppTitleSanitize :: String -> String
|
|
+ -- ^ escape / sanitizes input to 'ppTitle'
|
|
, ppLayout :: String -> String
|
|
-- ^ layout name format
|
|
, ppOrder :: [String] -> [String]
|
|
@@ -468,6 +482,7 @@ defaultPP = PP { ppCurrent = wrap "[" "]"
|
|
, ppSep = " : "
|
|
, ppWsSep = " "
|
|
, ppTitle = shorten 80
|
|
+ , ppTitleSanitize = xmobarStrip . dzenEscape
|
|
, ppLayout = id
|
|
, ppOrder = id
|
|
, ppOutput = putStrLn
|