module XMonad.Util.Dzen (
dzenConfig, DzenConfig,
timeout,
font,
xScreen,
vCenter,
hCenter,
center,
onCurr,
x,
y,
addArgs,
fgColor,
bgColor,
align,
slaveAlign,
lineCount,
dzen,
dzenScreen,
dzenWithArgs,
seconds,
chomp,
(>=>),
) where
import XMonad.Prelude
import XMonad
import XMonad.StackSet
import XMonad.Util.Run (runProcessWithInputAndWait, seconds)
import XMonad.Util.Font (Align (..))
type DzenConfig = (Int, [String]) -> X (Int, [String])
dzenConfig :: DzenConfig -> String -> X ()
dzenConfig :: DzenConfig -> String -> X ()
dzenConfig DzenConfig
conf String
s = do
(Int
t, [String]
args) <- DzenConfig
conf (Rational -> Int
seconds Rational
3, [])
String -> [String] -> String -> Int -> X ()
forall (m :: * -> *).
MonadIO m =>
String -> [String] -> String -> Int -> m ()
runProcessWithInputAndWait String
"dzen2" [String]
args (String -> String
chomp String
s) Int
t
chomp :: String -> String
chomp :: String -> String
chomp = (String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"\n") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char
'\n' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse
timeout :: Rational -> DzenConfig
timeout :: Rational -> DzenConfig
timeout = Int -> DzenConfig
timeoutMicro (Int -> DzenConfig) -> (Rational -> Int) -> Rational -> DzenConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Int
seconds
timeoutMicro :: Int -> DzenConfig
timeoutMicro :: Int -> DzenConfig
timeoutMicro Int
n (Int
_, [String]
ss) = DzenConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n, [String]
ss)
addArgs :: [String] -> DzenConfig
addArgs :: [String] -> DzenConfig
addArgs [String]
ss (Int
n, [String]
ss') = DzenConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n, [String]
ss [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
ss')
xScreen :: ScreenId -> DzenConfig
xScreen :: ScreenId -> DzenConfig
xScreen ScreenId
sc = [String] -> DzenConfig
addArgs [String
"-xs", Int -> String
forall a. Show a => a -> String
show (ScreenId -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ScreenId
sc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 :: Int)]
onCurr :: (ScreenId -> DzenConfig) -> DzenConfig
onCurr :: (ScreenId -> DzenConfig) -> DzenConfig
onCurr ScreenId -> DzenConfig
f (Int, [String])
conf = (XState -> ScreenId) -> X ScreenId
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
screen (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId)
-> (XState
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> XState
-> ScreenId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> (XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> XState
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
windowset) X ScreenId -> (ScreenId -> X (Int, [String])) -> X (Int, [String])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ScreenId -> DzenConfig)
-> (Int, [String]) -> ScreenId -> X (Int, [String])
forall a b c. (a -> b -> c) -> b -> a -> c
flip ScreenId -> DzenConfig
f (Int, [String])
conf
x :: Int -> DzenConfig
x :: Int -> DzenConfig
x Int
n = [String] -> DzenConfig
addArgs [String
"-x", Int -> String
forall a. Show a => a -> String
show Int
n]
y :: Int -> DzenConfig
y :: Int -> DzenConfig
y Int
n = [String] -> DzenConfig
addArgs [String
"-y", Int -> String
forall a. Show a => a -> String
show Int
n]
fgColor :: String -> DzenConfig
fgColor :: String -> DzenConfig
fgColor String
c = [String] -> DzenConfig
addArgs [String
"-fg", String
c]
bgColor :: String -> DzenConfig
bgColor :: String -> DzenConfig
bgColor String
c = [String] -> DzenConfig
addArgs [String
"-bg", String
c]
align :: Align -> DzenConfig
align :: Align -> DzenConfig
align = String -> Align -> DzenConfig
align' String
"-ta"
slaveAlign :: Align -> DzenConfig
slaveAlign :: Align -> DzenConfig
slaveAlign = String -> Align -> DzenConfig
align' String
"-sa"
align' :: String -> Align -> DzenConfig
align' :: String -> Align -> DzenConfig
align' String
opt Align
a = [String] -> DzenConfig
addArgs [String
opt, String
s] where
s :: String
s = case Align
a of
Align
AlignCenter -> String
"c"
Align
AlignLeft -> String
"l"
Align
AlignRight -> String
"r"
AlignRightOffset Int
_ -> String
"r"
font :: String -> DzenConfig
font :: String -> DzenConfig
font String
fn = [String] -> DzenConfig
addArgs [String
"-fn", String
fn]
vCenter :: Int -> ScreenId -> DzenConfig
vCenter :: Int -> ScreenId -> DzenConfig
vCenter = (Rectangle -> Dimension)
-> String -> String -> Int -> ScreenId -> DzenConfig
center' Rectangle -> Dimension
rect_height String
"-h" String
"-y"
hCenter :: Int -> ScreenId -> DzenConfig
hCenter :: Int -> ScreenId -> DzenConfig
hCenter = (Rectangle -> Dimension)
-> String -> String -> Int -> ScreenId -> DzenConfig
center' Rectangle -> Dimension
rect_width String
"-w" String
"-x"
center :: Int -> Int -> ScreenId -> DzenConfig
center :: Int -> Int -> ScreenId -> DzenConfig
center Int
width Int
height ScreenId
sc = Int -> ScreenId -> DzenConfig
hCenter Int
width ScreenId
sc DzenConfig -> DzenConfig -> DzenConfig
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Int -> ScreenId -> DzenConfig
vCenter Int
height ScreenId
sc
center' :: (Rectangle -> Dimension) -> String -> String -> Int -> ScreenId -> DzenConfig
center' :: (Rectangle -> Dimension)
-> String -> String -> Int -> ScreenId -> DzenConfig
center' Rectangle -> Dimension
selector String
extentName String
positionName Int
extent ScreenId
sc (Int, [String])
conf = do
Maybe Rectangle
rect <- (XState -> Maybe Rectangle) -> X (Maybe Rectangle)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (ScreenId
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Maybe Rectangle
detailFromScreenId ScreenId
sc (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Maybe Rectangle)
-> (XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> XState
-> Maybe Rectangle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
windowset)
case Maybe Rectangle
rect of
Maybe Rectangle
Nothing -> DzenConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (Int, [String])
conf
Just Rectangle
r -> [String] -> DzenConfig
addArgs
[String
extentName , Int -> String
forall a. Show a => a -> String
show Int
extent,
String
positionName, Int -> String
forall a. Show a => a -> String
show ((Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Rectangle -> Dimension
selector Rectangle
r) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
extent) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2),
String
"-xs" , Int -> String
forall a. Show a => a -> String
show (ScreenId -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ScreenId
sc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 :: Int)
] (Int, [String])
conf
detailFromScreenId :: ScreenId -> WindowSet -> Maybe Rectangle
detailFromScreenId :: ScreenId
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Maybe Rectangle
detailFromScreenId ScreenId
sc StackSet String (Layout Window) Window ScreenId ScreenDetail
ws = (ScreenDetail -> Rectangle)
-> Maybe ScreenDetail -> Maybe Rectangle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScreenDetail -> Rectangle
screenRect Maybe ScreenDetail
maybeSD where
c :: Screen String (Layout Window) Window ScreenId ScreenDetail
c = StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current StackSet String (Layout Window) Window ScreenId ScreenDetail
ws
v :: [Screen String (Layout Window) Window ScreenId ScreenDetail]
v = StackSet String (Layout Window) Window ScreenId ScreenDetail
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
visible StackSet String (Layout Window) Window ScreenId ScreenDetail
ws
mapping :: [(ScreenId, ScreenDetail)]
mapping = (Screen String (Layout Window) Window ScreenId ScreenDetail
-> (ScreenId, ScreenDetail))
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [(ScreenId, ScreenDetail)]
forall a b. (a -> b) -> [a] -> [b]
map (\Screen String (Layout Window) Window ScreenId ScreenDetail
s -> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
screen Screen String (Layout Window) Window ScreenId ScreenDetail
s, Screen String (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall i l a sid sd. Screen i l a sid sd -> sd
screenDetail Screen String (Layout Window) Window ScreenId ScreenDetail
s)) (Screen String (Layout Window) Window ScreenId ScreenDetail
cScreen String (Layout Window) Window ScreenId ScreenDetail
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a. a -> [a] -> [a]
:[Screen String (Layout Window) Window ScreenId ScreenDetail]
v)
maybeSD :: Maybe ScreenDetail
maybeSD = ScreenId -> [(ScreenId, ScreenDetail)] -> Maybe ScreenDetail
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ScreenId
sc [(ScreenId, ScreenDetail)]
mapping
lineCount :: Int -> DzenConfig
lineCount :: Int -> DzenConfig
lineCount Int
n = [String] -> DzenConfig
addArgs [String
"-l", Int -> String
forall a. Show a => a -> String
show Int
n]
dzen :: String -> Int -> X ()
dzen :: String -> Int -> X ()
dzen = (Int -> String -> X ()) -> String -> Int -> X ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (DzenConfig -> String -> X ()
dzenConfig (DzenConfig -> String -> X ())
-> (Int -> DzenConfig) -> Int -> String -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> DzenConfig
timeoutMicro)
dzenWithArgs :: String -> [String] -> Int -> X ()
dzenWithArgs :: String -> [String] -> Int -> X ()
dzenWithArgs String
str [String]
args Int
t = DzenConfig -> String -> X ()
dzenConfig (Int -> DzenConfig
timeoutMicro Int
t DzenConfig -> DzenConfig -> DzenConfig
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> [String] -> DzenConfig
addArgs [String]
args) String
str
dzenScreen :: ScreenId -> String -> Int -> X ()
dzenScreen :: ScreenId -> String -> Int -> X ()
dzenScreen ScreenId
sc String
str Int
t = DzenConfig -> String -> X ()
dzenConfig (Int -> DzenConfig
timeoutMicro Int
t DzenConfig -> DzenConfig -> DzenConfig
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ScreenId -> DzenConfig
xScreen ScreenId
sc) String
str