{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
module XMonad.Hooks.StatusBar.PP (
PP(..), def,
dynamicLogString,
dynamicLogString',
dynamicLogWithPP,
WS(..), WSPP, WSPP', fallbackPrinters,
isUrgent, isCurrent, isVisible, isVisibleNoWindows, isHidden,
dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
wrap, pad, trim, shorten, shorten', shortenLeft, shortenLeft',
xmobarColor, xmobarFont, xmobarAction, xmobarBorder,
xmobarRaw, xmobarStrip, xmobarStripTags,
dzenColor, dzenEscape, dzenStrip, filterOutWsPP,
pprWindowSet,
pprWindowSetXinerama
) where
import Control.Monad.Reader
import Control.DeepSeq
import qualified Data.List.NonEmpty as NE
import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as S
import XMonad.Util.NamedWindows
import XMonad.Util.WorkspaceCompare
import XMonad.Hooks.UrgencyHook
data PP = PP { PP -> String -> String
ppCurrent :: WorkspaceId -> String
, PP -> String -> String
ppVisible :: WorkspaceId -> String
, PP -> String -> String
ppHidden :: WorkspaceId -> String
, PP -> String -> String
ppHiddenNoWindows :: WorkspaceId -> String
, PP -> Maybe (String -> String)
ppVisibleNoWindows :: Maybe (WorkspaceId -> String)
, PP -> String -> String
ppUrgent :: WorkspaceId -> String
, PP -> String -> WindowSpace -> String
ppRename :: String -> WindowSpace -> String
, PP -> String
ppSep :: String
, PP -> String
ppWsSep :: String
, PP -> String -> String
ppTitle :: String -> String
, PP -> String -> String
ppTitleSanitize :: String -> String
, PP -> String -> String
ppLayout :: String -> String
, PP -> [String] -> [String]
ppOrder :: [String] -> [String]
, PP -> X ([WindowSpace] -> [WindowSpace])
ppSort :: X ([WindowSpace] -> [WindowSpace])
, :: [X (Maybe String)]
, PP -> String -> IO ()
ppOutput :: String -> IO ()
, PP -> WSPP
ppPrinters :: WSPP
}
instance Default PP where
def :: PP
def = PP { ppCurrent :: String -> String
ppCurrent = String -> String -> String -> String
wrap String
"[" String
"]"
, ppVisible :: String -> String
ppVisible = String -> String -> String -> String
wrap String
"<" String
">"
, ppHidden :: String -> String
ppHidden = forall a. a -> a
id
, ppHiddenNoWindows :: String -> String
ppHiddenNoWindows = forall a b. a -> b -> a
const String
""
, ppVisibleNoWindows :: Maybe (String -> String)
ppVisibleNoWindows = forall a. Maybe a
Nothing
, ppUrgent :: String -> String
ppUrgent = forall a. a -> a
id
, ppRename :: String -> WindowSpace -> String
ppRename = forall (f :: * -> *) a. Applicative f => a -> f a
pure
, ppSep :: String
ppSep = String
" : "
, ppWsSep :: String
ppWsSep = String
" "
, ppTitle :: String -> String
ppTitle = Int -> String -> String
shorten Int
80
, ppTitleSanitize :: String -> String
ppTitleSanitize = String -> String
xmobarStrip forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
dzenEscape
, ppLayout :: String -> String
ppLayout = forall a. a -> a
id
, ppOrder :: [String] -> [String]
ppOrder = forall a. a -> a
id
, ppOutput :: String -> IO ()
ppOutput = String -> IO ()
putStrLn
, ppSort :: X ([WindowSpace] -> [WindowSpace])
ppSort = X ([WindowSpace] -> [WindowSpace])
getSortByIndex
, ppExtras :: [X (Maybe String)]
ppExtras = []
, ppPrinters :: WSPP
ppPrinters = forall (f :: * -> *) a. Alternative f => f a
empty
}
dynamicLogWithPP :: PP -> X ()
dynamicLogWithPP :: PP -> X ()
dynamicLogWithPP PP
pp = PP -> X String
dynamicLogString PP
pp forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. MonadIO m => IO a -> m a
io forall b c a. (b -> c) -> (a -> b) -> a -> c
. PP -> String -> IO ()
ppOutput PP
pp
dynamicLogString :: PP -> X String
dynamicLogString :: PP -> X String
dynamicLogString PP
pp = forall a. a -> X a -> X a
userCodeDef String
"_|_" (PP -> X String
dynamicLogString' PP
pp)
dynamicLogString' :: PP -> X String
dynamicLogString' :: PP -> X String
dynamicLogString' PP
pp = do
WindowSet
winset <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
[Window]
urgents <- X [Window]
readUrgents
[WindowSpace] -> [WindowSpace]
sort' <- PP -> X ([WindowSpace] -> [WindowSpace])
ppSort PP
pp
let ld :: String
ld = forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> String
description forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> l
S.layout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current forall a b. (a -> b) -> a -> b
$ WindowSet
winset
let ws :: String
ws = ([WindowSpace] -> [WindowSpace])
-> [Window] -> PP -> WindowSet -> String
pprWindowSet [WindowSpace] -> [WindowSpace]
sort' [Window]
urgents PP
pp WindowSet
winset
[Maybe String]
extras <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall a. a -> X a -> X a
userCodeDef forall a. Maybe a
Nothing) forall a b. (a -> b) -> a -> b
$ PP -> [X (Maybe String)]
ppExtras PP
pp
String
wt <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"") (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> X NamedWindow
getName) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a s sd. StackSet i l a s sd -> Maybe a
S.peek forall a b. (a -> b) -> a -> b
$ WindowSet
winset
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a. NFData a => a -> a
force forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
sepBy (PP -> String
ppSep PP
pp) forall b c a. (b -> c) -> (a -> b) -> a -> c
. PP -> [String] -> [String]
ppOrder PP
pp forall a b. (a -> b) -> a -> b
$
[ String
ws
, PP -> String -> String
ppLayout PP
pp String
ld
, PP -> String -> String
ppTitle PP
pp forall a b. (a -> b) -> a -> b
$ PP -> String -> String
ppTitleSanitize PP
pp String
wt
]
forall a. [a] -> [a] -> [a]
++ forall a. [Maybe a] -> [a]
catMaybes [Maybe String]
extras
pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
pprWindowSet :: ([WindowSpace] -> [WindowSpace])
-> [Window] -> PP -> WindowSet -> String
pprWindowSet [WindowSpace] -> [WindowSpace]
sort' [Window]
urgents PP
pp WindowSet
s = String -> [String] -> String
sepBy (PP -> String
ppWsSep PP
pp) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map WindowSpace -> String
fmt forall b c a. (b -> c) -> (a -> b) -> a -> c
. [WindowSpace] -> [WindowSpace]
sort' forall a b. (a -> b) -> a -> b
$
forall a b. (a -> b) -> [a] -> [b]
map forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace (forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current WindowSet
s forall a. a -> [a] -> [a]
: forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
S.visible WindowSet
s) forall a. [a] -> [a] -> [a]
++ forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
S.hidden WindowSet
s
where
fmt :: WindowSpace -> String
fmt :: WindowSpace -> String
fmt WindowSpace
w = String -> String
pr (PP -> String -> WindowSpace -> String
ppRename PP
pp (forall i l a. Workspace i l a -> i
S.tag WindowSpace
w) WindowSpace
w)
where
printers :: WSPP
printers = PP -> WSPP
ppPrinters PP
pp forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WSPP
fallbackPrinters
pr :: String -> String
pr = forall a. a -> Maybe a -> a
fromMaybe forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT WSPP
printers forall a b. (a -> b) -> a -> b
$
WS{ wsUrgents :: [Window]
wsUrgents = [Window]
urgents, wsWindowSet :: WindowSet
wsWindowSet = WindowSet
s, wsWS :: WindowSpace
wsWS = WindowSpace
w, wsPP :: PP
wsPP = PP
pp }
data WS = WS{ WS -> [Window]
wsUrgents :: [Window]
, WS -> WindowSet
wsWindowSet :: WindowSet
, WS -> WindowSpace
wsWS :: WindowSpace
, WS -> PP
wsPP :: PP
}
type WSPP' = ReaderT WS Maybe
type WSPP = WSPP' (WorkspaceId -> String)
fallbackPrinters :: WSPP
fallbackPrinters :: WSPP
fallbackPrinters = WS -> Bool
isUrgent forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> PP -> String -> String
ppUrgent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WS -> Bool
isCurrent' forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> PP -> String -> String
ppCurrent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WS -> Bool
isVisible' forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> PP -> String -> String
ppVisible
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WS -> Bool
isVisibleNoWindows' forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. a -> Maybe a -> a
fromMaybe PP -> String -> String
ppVisible PP -> Maybe (String -> String)
ppVisibleNoWindows
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WS -> Bool
isHidden' forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> PP -> String -> String
ppHidden
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True forall {f :: * -> *} {b}.
(MonadReader WS f, Alternative f) =>
(WS -> Bool) -> (PP -> b) -> f b
?-> PP -> String -> String
ppHiddenNoWindows
where
WS -> Bool
cond ?-> :: (WS -> Bool) -> (PP -> b) -> f b
?-> PP -> b
ppr = (forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WS -> Bool
cond forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *). Alternative f => Bool -> f ()
guard) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (PP -> b
ppr forall b c a. (b -> c) -> (a -> b) -> a -> c
. WS -> PP
wsPP)
isUrgent :: WS -> Bool
isUrgent :: WS -> Bool
isUrgent WS{[Window]
WindowSet
WindowSpace
PP
wsPP :: PP
wsWS :: WindowSpace
wsWindowSet :: WindowSet
wsUrgents :: [Window]
wsPP :: WS -> PP
wsWS :: WS -> WindowSpace
wsWindowSet :: WS -> WindowSet
wsUrgents :: WS -> [Window]
..} = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Window
x -> (forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just (forall i l a. Workspace i l a -> i
S.tag WindowSpace
wsWS)) (forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Maybe i
S.findTag Window
x WindowSet
wsWindowSet)) [Window]
wsUrgents
isCurrent' :: WS -> Bool
isCurrent' :: WS -> Bool
isCurrent' WS{[Window]
WindowSet
WindowSpace
PP
wsPP :: PP
wsWS :: WindowSpace
wsWindowSet :: WindowSet
wsUrgents :: [Window]
wsPP :: WS -> PP
wsWS :: WS -> WindowSpace
wsWindowSet :: WS -> WindowSet
wsUrgents :: WS -> [Window]
..} = forall i l a. Workspace i l a -> i
S.tag WindowSpace
wsWS forall a. Eq a => a -> a -> Bool
== forall i l a s sd. StackSet i l a s sd -> i
S.currentTag WindowSet
wsWindowSet
isCurrent :: WS -> Bool
isCurrent :: WS -> Bool
isCurrent = (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isUrgent) forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> WS -> Bool
isCurrent'
isVisible' :: WS -> Bool
isVisible' :: WS -> Bool
isVisible' = WS -> Bool
isVisibleNoWindows' forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> Maybe (Stack a)
S.stack forall b c a. (b -> c) -> (a -> b) -> a -> c
. WS -> WindowSpace
wsWS
isVisible :: WS -> Bool
isVisible :: WS -> Bool
isVisible = (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isUrgent) forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isCurrent') forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> WS -> Bool
isVisible'
isVisibleNoWindows' :: WS -> Bool
isVisibleNoWindows' :: WS -> Bool
isVisibleNoWindows' WS{[Window]
WindowSet
WindowSpace
PP
wsPP :: PP
wsWS :: WindowSpace
wsWindowSet :: WindowSet
wsUrgents :: [Window]
wsPP :: WS -> PP
wsWS :: WS -> WindowSpace
wsWindowSet :: WS -> WindowSet
wsUrgents :: WS -> [Window]
..} = forall i l a. Workspace i l a -> i
S.tag WindowSpace
wsWS forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
visibles
where visibles :: [String]
visibles = forall a b. (a -> b) -> [a] -> [b]
map (forall i l a. Workspace i l a -> i
S.tag forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace) (forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
S.visible WindowSet
wsWindowSet)
isVisibleNoWindows :: WS -> Bool
isVisibleNoWindows :: WS -> Bool
isVisibleNoWindows =
(Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isUrgent)
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isCurrent')
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isVisible')
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> WS -> Bool
isVisibleNoWindows'
isHidden' :: WS -> Bool
isHidden' :: WS -> Bool
isHidden' = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> Maybe (Stack a)
S.stack forall b c a. (b -> c) -> (a -> b) -> a -> c
. WS -> WindowSpace
wsWS
isHidden :: WS -> Bool
isHidden :: WS -> Bool
isHidden =
(Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isUrgent)
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isCurrent')
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isVisible')
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WS -> Bool
isVisibleNoWindows')
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
<&&> WS -> Bool
isHidden'
pprWindowSetXinerama :: WindowSet -> String
pprWindowSetXinerama :: WindowSet -> String
pprWindowSetXinerama WindowSet
ws = String
"[" forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
onscreen forall a. [a] -> [a] -> [a]
++ String
"] " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
offscreen
where onscreen :: [String]
onscreen = forall a b. (a -> b) -> [a] -> [b]
map (forall i l a. Workspace i l a -> i
S.tag forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn forall i l a sid sd. Screen i l a sid sd -> sid
S.screen forall a b. (a -> b) -> a -> b
$ forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current WindowSet
ws forall a. a -> [a] -> [a]
: forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
S.visible WindowSet
ws
offscreen :: [String]
offscreen = forall a b. (a -> b) -> [a] -> [b]
map forall i l a. Workspace i l a -> i
S.tag forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> Maybe (Stack a)
S.stack)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn forall i l a. Workspace i l a -> i
S.tag forall a b. (a -> b) -> a -> b
$ forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
S.hidden WindowSet
ws
wrap :: String
-> String
-> String
-> String
wrap :: String -> String -> String -> String
wrap String
_ String
_ String
"" = String
""
wrap String
l String
r String
m = String
l forall a. [a] -> [a] -> [a]
++ String
m forall a. [a] -> [a] -> [a]
++ String
r
pad :: String -> String
pad :: String -> String
pad = String -> String -> String -> String
wrap String
" " String
" "
trim :: String -> String
trim :: String -> String
trim = String -> String
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
f
where f :: String -> String
f = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace
shorten :: Int -> String -> String
shorten :: Int -> String -> String
shorten = String -> Int -> String -> String
shorten' String
"..."
shorten' :: String -> Int -> String -> String
shorten' :: String -> Int -> String -> String
shorten' String
end Int
n String
xs | forall (t :: * -> *) a. Foldable t => t a -> Int
length String
xs forall a. Ord a => a -> a -> Bool
< Int
n = String
xs
| Bool
otherwise = forall a. Int -> [a] -> [a]
take (Int
n forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length String
end) String
xs forall a. [a] -> [a] -> [a]
++ String
end
shortenLeft :: Int -> String -> String
shortenLeft :: Int -> String -> String
shortenLeft = String -> Int -> String -> String
shortenLeft' String
"..."
shortenLeft' :: String -> Int -> String -> String
shortenLeft' :: String -> Int -> String -> String
shortenLeft' String
end Int
n String
xs | Int
l forall a. Ord a => a -> a -> Bool
< Int
n = String
xs
| Bool
otherwise = String
end forall a. [a] -> [a] -> [a]
++ forall a. Int -> [a] -> [a]
drop (Int
l forall a. Num a => a -> a -> a
- Int
n forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length String
end) String
xs
where l :: Int
l = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
xs
sepBy :: String
-> [String]
-> String
sepBy :: String -> [String] -> String
sepBy String
sep = forall a. [a] -> [[a]] -> [a]
intercalate String
sep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null)
dzenColor :: String
-> String
-> String
-> String
dzenColor :: String -> String -> String -> String
dzenColor String
fg String
bg = String -> String -> String -> String
wrap (String
fg1forall a. [a] -> [a] -> [a]
++String
bg1) (String
fg2forall a. [a] -> [a] -> [a]
++String
bg2)
where (String
fg1,String
fg2) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
fg = (String
"",String
"")
| Bool
otherwise = (String
"^fg(" forall a. [a] -> [a] -> [a]
++ String
fg forall a. [a] -> [a] -> [a]
++ String
")",String
"^fg()")
(String
bg1,String
bg2) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
bg = (String
"",String
"")
| Bool
otherwise = (String
"^bg(" forall a. [a] -> [a] -> [a]
++ String
bg forall a. [a] -> [a] -> [a]
++ String
")",String
"^bg()")
dzenEscape :: String -> String
dzenEscape :: String -> String
dzenEscape = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Char
x -> if Char
x forall a. Eq a => a -> a -> Bool
== Char
'^' then String
"^^" else [Char
x])
dzenStrip :: String -> String
dzenStrip :: String -> String
dzenStrip = String -> String -> String
strip [] where
strip :: String -> String -> String
strip String
keep String
x
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
x = String
keep
| String
"^^" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x = String -> String -> String
strip (String
keep forall a. [a] -> [a] -> [a]
++ String
"^") (forall a. Int -> [a] -> [a]
drop Int
2 String
x)
| String
"^" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x = String -> String -> String
strip String
keep (forall a. Int -> [a] -> [a]
drop Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
/= Char
')') forall a b. (a -> b) -> a -> b
$ String
x)
| Bool
otherwise = let (String
good,String
x') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
'^') String
x
in String -> String -> String
strip (String
keep forall a. [a] -> [a] -> [a]
++ String
good) String
x'
xmobarFont :: Int
-> String
-> String
xmobarFont :: Int -> String -> String
xmobarFont Int
index = String -> String -> String -> String
wrap (String
"<fn=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
index forall a. [a] -> [a] -> [a]
++ String
">") String
"</fn>"
xmobarColor :: String
-> String
-> String
-> String
xmobarColor :: String -> String -> String -> String
xmobarColor String
fg String
bg = String -> String -> String -> String
wrap String
t String
"</fc>"
where t :: String
t = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"<fc=", String
fg, if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
bg then String
"" else String
"," forall a. [a] -> [a] -> [a]
++ String
bg, String
">"]
xmobarAction :: String
-> String
-> String
-> String
xmobarAction :: String -> String -> String -> String
xmobarAction String
command String
button = String -> String -> String -> String
wrap String
l String
r
where
l :: String
l = String
"<action=`" forall a. [a] -> [a] -> [a]
++ String
command forall a. [a] -> [a] -> [a]
++ String
"` button=" forall a. [a] -> [a] -> [a]
++ String
button forall a. [a] -> [a] -> [a]
++ String
">"
r :: String
r = String
"</action>"
xmobarBorder :: String
-> String
-> Int
-> String
-> String
xmobarBorder :: String -> String -> Int -> String -> String
xmobarBorder String
border String
color Int
width = String -> String -> String -> String
wrap String
prefix String
"</box>"
where
prefix :: String
prefix = String
"<box type=" forall a. [a] -> [a] -> [a]
++ String
border forall a. [a] -> [a] -> [a]
++ String
" width=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
width forall a. [a] -> [a] -> [a]
++ String
" color="
forall a. [a] -> [a] -> [a]
++ String
color forall a. [a] -> [a] -> [a]
++ String
">"
xmobarRaw :: String -> String
xmobarRaw :: String -> String
xmobarRaw String
"" = String
""
xmobarRaw String
s = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"<raw=", forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s, String
":", String
s, String
"/>"]
xmobarStrip :: String -> String
xmobarStrip :: String -> String
xmobarStrip = forall a. Eq a => (a -> a) -> a -> a
converge ([String] -> String -> String
xmobarStripTags [String
"fc",String
"icon",String
"action"])
converge :: (Eq a) => (a -> a) -> a -> a
converge :: forall a. Eq a => (a -> a) -> a -> a
converge a -> a
f a
a
= forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> a
NE.head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => [a] -> NonEmpty a
notEmpty
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Eq a => a -> a -> Bool
(/=))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [a]
xs
forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop Int
1 [a]
xs
where xs :: [a]
xs = forall a. (a -> a) -> a -> [a]
iterate a -> a
f a
a
xmobarStripTags :: [String]
-> String -> String
xmobarStripTags :: [String] -> String -> String
xmobarStripTags [String]
tags = String -> String -> String
strip [] where
strip :: String -> String -> String
strip String
keep [] = String
keep
strip String
keep String
x
| String
rest: [String]
_ <- forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe String -> Maybe String
dropTag [String]
tags = String -> String -> String
strip String
keep String
rest
| Char
'<':String
xs <- String
x = String -> String -> String
strip (String
keep forall a. [a] -> [a] -> [a]
++ String
"<") String
xs
| (String
good,String
x') <- forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
'<') String
x = String -> String -> String
strip (String
keep forall a. [a] -> [a] -> [a]
++ String
good) String
x'
where dropTag :: String -> Maybe String
dropTag :: String -> Maybe String
dropTag String
tag = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> String
dropTilClose (String -> String
openTag String
tag forall a. Eq a => [a] -> [a] -> Maybe [a]
`stripPrefix` String
x),
String -> String
closeTag String
tag forall a. Eq a => [a] -> [a] -> Maybe [a]
`stripPrefix` String
x]
dropTilClose, openTag, closeTag :: String -> String
dropTilClose :: String -> String
dropTilClose = forall a. Int -> [a] -> [a]
drop Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
/= Char
'>')
openTag :: String -> String
openTag String
str = String
"<" forall a. [a] -> [a] -> [a]
++ String
str forall a. [a] -> [a] -> [a]
++ String
"="
closeTag :: String -> String
closeTag String
str = String
"</" forall a. [a] -> [a] -> [a]
++ String
str forall a. [a] -> [a] -> [a]
++ String
">"
filterOutWsPP :: [WorkspaceId] -> PP -> PP
filterOutWsPP :: [String] -> PP -> PP
filterOutWsPP [String]
ws PP
pp = PP
pp { ppSort :: X ([WindowSpace] -> [WindowSpace])
ppSort = (forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [WindowSpace] -> [WindowSpace]
filterOutWs [String]
ws) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PP -> X ([WindowSpace] -> [WindowSpace])
ppSort PP
pp }
dzenPP :: PP
dzenPP :: PP
dzenPP = forall a. Default a => a
def
{ ppCurrent :: String -> String
ppCurrent = String -> String -> String -> String
dzenColor String
"white" String
"#2b4f98" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppVisible :: String -> String
ppVisible = String -> String -> String -> String
dzenColor String
"black" String
"#999999" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppHidden :: String -> String
ppHidden = String -> String -> String -> String
dzenColor String
"black" String
"#cccccc" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppHiddenNoWindows :: String -> String
ppHiddenNoWindows = forall a b. a -> b -> a
const String
""
, ppUrgent :: String -> String
ppUrgent = String -> String -> String -> String
dzenColor String
"red" String
"yellow" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppWsSep :: String
ppWsSep = String
""
, ppSep :: String
ppSep = String
""
, ppLayout :: String -> String
ppLayout = String -> String -> String -> String
dzenColor String
"black" String
"#cccccc"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\String
x -> String -> String
pad forall a b. (a -> b) -> a -> b
$ case String
x of
String
"TilePrime Horizontal" -> String
"TTT"
String
"TilePrime Vertical" -> String
"[]="
String
"Hinted Full" -> String
"[ ]"
String
_ -> String
x
)
, ppTitle :: String -> String
ppTitle = (String
"^bg(#324c80) " forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
dzenEscape
}
xmobarPP :: PP
xmobarPP :: PP
xmobarPP = forall a. Default a => a
def { ppCurrent :: String -> String
ppCurrent = String -> String -> String -> String
xmobarColor String
"yellow" String
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String -> String
wrap String
"[" String
"]"
, ppTitle :: String -> String
ppTitle = String -> String -> String -> String
xmobarColor String
"green" String
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
shorten Int
40
, ppVisible :: String -> String
ppVisible = String -> String -> String -> String
wrap String
"(" String
")"
, ppUrgent :: String -> String
ppUrgent = String -> String -> String -> String
xmobarColor String
"red" String
"yellow"
}
sjanssenPP :: PP
sjanssenPP :: PP
sjanssenPP = forall a. Default a => a
def { ppCurrent :: String -> String
ppCurrent = String -> String -> String -> String
xmobarColor String
"white" String
"black"
, ppTitle :: String -> String
ppTitle = String -> String -> String -> String
xmobarColor String
"#00ee00" String
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
shorten Int
120
}
byorgeyPP :: PP
byorgeyPP :: PP
byorgeyPP = forall a. Default a => a
def { ppHiddenNoWindows :: String -> String
ppHiddenNoWindows = String -> String
showNamedWorkspaces
, ppHidden :: String -> String
ppHidden = String -> String -> String -> String
dzenColor String
"black" String
"#a8a3f7" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppCurrent :: String -> String
ppCurrent = String -> String -> String -> String
dzenColor String
"yellow" String
"#a8a3f7" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppUrgent :: String -> String
ppUrgent = String -> String -> String -> String
dzenColor String
"red" String
"yellow" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad
, ppSep :: String
ppSep = String
" | "
, ppWsSep :: String
ppWsSep = String
""
, ppTitle :: String -> String
ppTitle = Int -> String -> String
shorten Int
70
, ppOrder :: [String] -> [String]
ppOrder = forall a. [a] -> [a]
reverse
}
where
showNamedWorkspaces :: String -> String
showNamedWorkspaces String
wsId =
if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
wsId) [Char
'a' .. Char
'z'] then String -> String
pad String
wsId else String
""