aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/Dzen.hs
blob: a7fb3db769465618c777be7a67e434f98a1518c6 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Util.Dzen
-- Copyright   :  (c) glasser@mit.edu
-- License     :  BSD
--
-- Maintainer  :  glasser@mit.edu
-- Stability   :  stable
-- Portability :  unportable
--
-- Handy wrapper for dzen. Requires dzen >= 0.2.4.
--
-----------------------------------------------------------------------------

module XMonad.Util.Dzen (
    -- * Flexible interface
    dzenConfig,
    timeout,
    font,
    xScreen,
    vCenter,
    hCenter,
    center,
    onCurr,
    x,
    y,
    addArgs,

    -- * Legacy interface
    dzen,
    dzenScreen,
    dzenWithArgs,

    -- * Miscellaneous
    seconds,
    chomp,
    (>=>)
  ) where

import Control.Monad
import Data.List
import XMonad
import XMonad.StackSet
import XMonad.Util.Run (runProcessWithInputAndWait, seconds)

type DzenConfig = (Int, [String]) -> X (Int, [String])

-- | @dzenConfig config s@ will display the string @s@ according to the
-- configuration @config@.  For example, to display the string @\"foobar\"@ with
-- all the default settings, you can simply call
--
-- > dzenConfig return "foobar"
--
-- Or, to set a longer timeout, you could use
--
-- > dzenConfig (timeout 10) "foobar"
--
-- You can combine configurations with the (>=>) operator.  To display
-- @\"foobar\"@ for 10 seconds on the first screen, you could use
--
-- > dzenConfig (timeout 10 >=> xScreen 0) "foobar"
--
-- As a final example, you could adapt the above to display @\"foobar\"@ for
-- 10 seconds on the current screen with
--
-- > dzenConfig (timeout 10 >=> onCurr xScreen) "foobar"
dzenConfig :: DzenConfig -> String -> X ()
dzenConfig conf s = do
    (t, args) <- conf (seconds 3, [])
    runProcessWithInputAndWait "dzen2" args (chomp s) t

-- | dzen wants exactly one newline at the end of its input, so this can be
-- used for your own invocations of dzen.  However, all functions in this
-- module will call this for you.
chomp :: String -> String
chomp = (++"\n") . reverse . dropWhile ('\n' ==) . reverse

-- | Set the timeout, in seconds.  This defaults to 3 seconds if not
-- specified.
timeout :: Rational -> DzenConfig
timeout = timeoutMicro . seconds

-- | Set the timeout, in microseconds.  Mostly here for the legacy
-- interface.
timeoutMicro :: Int -> DzenConfig
timeoutMicro n (_, ss) = return (n, ss)

-- | Add raw command-line arguments to the configuration.  These will be
-- passed on verbatim to dzen2.  The default includes no arguments.
addArgs :: [String] -> DzenConfig
addArgs ss (n, ss') = return (n, ss ++ ss')

-- | Start dzen2 on a particular screen.  Only works with versions of dzen
-- that support the "-xs" argument.
xScreen :: ScreenId -> DzenConfig
xScreen sc = addArgs ["-xs", show (fromIntegral sc + 1 :: Int)]

-- | Take a screen-specific configuration and supply it with the screen ID
-- of the currently focused screen, according to xmonad.  For example, show
-- a 100-pixel wide bar centered within the current screen, you could use
--
-- > dzenConfig (onCurr (hCenter 100)) "foobar"
--
-- Of course, you can still combine these with (>=>); for example, to center
-- the string @\"foobar\"@ both horizontally and vertically in a 100x14 box
-- using the lovely Terminus font, you could use
--
-- > terminus = "-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*"
-- > dzenConfig (onCurr (center 100 14) >=> font terminus) "foobar"
onCurr :: (ScreenId -> DzenConfig) -> DzenConfig
onCurr f conf = gets (screen . current . windowset) >>= flip f conf

-- | Put the top of the dzen bar at a particular pixel.
x :: Int -> DzenConfig
x n = addArgs ["-x", show n]
-- | Put the left of the dzen bar at a particular pixel.
y :: Int -> DzenConfig
y n = addArgs ["-y", show n]

-- | Specify the font.  Check out xfontsel to get the format of the String
-- right; if your dzen supports xft, then you can supply that here, too.
font :: String -> DzenConfig
font fn = addArgs ["-fn", fn]

-- | @vCenter height sc@ sets the configuration to have the dzen bar appear
-- on screen @sc@ with height @height@, vertically centered with respect to
-- the actual size of that screen.
vCenter :: Int -> ScreenId -> DzenConfig
vCenter = center' rect_height "-h" "-y"

-- | @hCenter width sc@ sets the configuration to have the dzen bar appear
-- on screen @sc@ with width @width@, horizontally centered with respect to
-- the actual size of that screen.
hCenter :: Int -> ScreenId -> DzenConfig
hCenter = center' rect_width  "-w" "-x"

-- | @center width height sc@ sets the configuration to have the dzen bar
-- appear on screen @sc@ with width @width@ and height @height@, centered
-- both horizontally and vertically with respect to the actual size of that
-- screen.
center :: Int -> Int -> ScreenId -> DzenConfig
center width height sc = hCenter width sc >=> vCenter height sc

-- Center things along a single dimension on a particular screen.
center' :: (Rectangle -> Dimension) -> String -> String -> Int -> ScreenId -> DzenConfig
center' selector extentName positionName extent sc conf = do
    rect <- gets (detailFromScreenId sc . windowset)
    case rect of
        Nothing -> return conf
        Just r  -> addArgs
            [extentName  , show extent,
             positionName, show ((fromIntegral (selector r) - extent) `div` 2),
             "-xs"       , show (fromIntegral sc + 1 :: Int)
            ] conf

-- Get the rectangle outlining a particular screen.
detailFromScreenId :: ScreenId -> WindowSet -> Maybe Rectangle
detailFromScreenId sc ws = fmap screenRect maybeSD where
    c       = current ws
    v       = visible ws
    mapping = map (\s -> (screen s, screenDetail s)) (c:v)
    maybeSD = lookup sc mapping

-- | @dzen str timeout@ pipes @str@ to dzen2 for @timeout@ microseconds.
-- Example usage:
--
-- > dzen "Hi, mom!" (5 `seconds`)
dzen :: String -> Int -> X ()
dzen = flip (dzenConfig . timeoutMicro)

-- | @dzen str args timeout@ pipes @str@ to dzen2 for @timeout@ seconds, passing @args@ to dzen.
-- Example usage:
--
-- > dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`)
dzenWithArgs :: String -> [String] -> Int -> X ()
dzenWithArgs str args t = dzenConfig (timeoutMicro t >=> addArgs args) str

-- | @dzenScreen sc str timeout@ pipes @str@ to dzen2 for @timeout@ microseconds, and on screen @sc@.
-- Requires dzen to be compiled with Xinerama support.
dzenScreen :: ScreenId -> String -> Int -> X ()
dzenScreen sc str t = dzenConfig (timeoutMicro t >=> xScreen sc) str