Codebase list xmobar / upstream/0.23.1
Imported Upstream version 0.23.1 Apollon Oikonomopoulos 9 years ago
12 changed file(s) with 81 addition(s) and 52 deletion(s). Raw diff Collapse all Expand all
00 % xmobar - Release notes
1
2 ## Version 0.23.1 (Apr 14, 2015)
3
4 _Bug fixes_
5
6 - Vertical alignment for icons, [issue #216]
7 - Improvements to vertical text alignment, with many thanks to Jan
8 Palus (see ongoing discussion in [issue #221]).
9 - Better error handling in `Volume` monitor, [issue #215]
10 - Compilation with ghc 7.8 and 7.10 (thanks to Edward Tjörnhammar,
11 see [issue #225]).
12
13 [issue #225]: https://github.com/jaor/xmobar/issues/225
14 [issue #221]: https://github.com/jaor/xmobar/issues/221
15 [issue #216]: https://github.com/jaor/xmobar/issues/216
16 [issue #215]: https://github.com/jaor/xmobar/issues/215
117
218 ## Version 0.23 (Mar 8, 2015)
319
99 features, like dynamic color management, icons, output templates, and
1010 extensibility through plugins.
1111
12 This page documents xmobar 0.23 (see [release notes]).
12 This page documents xmobar 0.23.1 (see [release notes]).
1313
1414 [This screenshot] shows xmobar running under [sawfish], with
1515 antialiased fonts. And [this one] is my desktop with [xmonad] and two
197197 - `<fc=#FF0000>string</fc>` will print `string` with `#FF0000` color
198198 (red).
199199
200 - `<fn=1>string</fn>` will print `string` with the first font from `additionalFonts`.
201 The index `0` corresponds to the standard font.
200 - `<fn=1>string</fn>` will print `string` with the first font from
201 `additionalFonts`. The index `0` corresponds to the standard font.
202202
203203 - `<icon=/path/to/icon.xbm/>` will insert the given bitmap. XPM image
204204 format is also supported when compiled with `--flags="with_xpm"`.
205205
206 - ```<action=`command` button=12345>``` will execute given command when
207 clicked with specified buttons. If not specified, button is equal to 1
208 (left mouse button). Using old syntax (without backticks surrounding `command`)
209 will result in `button` attribute being ignored.
206 - ```<action=`command` button=12345>``` will execute given command
207 when clicked with specified buttons. If not specified, button is
208 equal to 1 (left mouse button). Using old syntax (without backticks
209 surrounding `command`) will result in `button` attribute being
210 ignored.
210211
211212 - `<raw=len:str/>` allows the encapsulation of arbitrary text `str` (which
212213 must be `len` `Char`s long, where `len` is encoded as a decimal sequence).
218219
219220 and receives on standard input the line
220221
221 ```<action=`echo test` button=1><raw=41:<action=`echo mooo`
222 button=1>foo</action>/></action>```
222 ```<action=`echo test` button=1><raw=41:<action=`echo mooo` button=1>foo</action>/></action>```
223223
224224 then it will display the text ```<action=`echo mooo` button=1>foo</action>```,
225225 which, when clicked, will cause `test` to be echoed.
15261526 Perner, Jens Petersen, Alexander Polakov, Petr Rockai, Andrew
15271527 Sackville-West, Markus Scherer, Alexander Shabalin, Peter Simons,
15281528 Alexander Solovyov, John Soros, Travis Staton, Artem Tarasov, Samuli
1529 Thomasson, Sergei Trofimovich, Thomas Tuegel, Jan Vornberger, Anton
1530 Vorontsov, Daniel Wagner, Phil Xiaojun Hu, Edward Z. Yang and Norbert
1531 Zeh.
1529 Thomasson, Edward Tjörnhammar, Sergei Trofimovich, Thomas Tuegel, Jan
1530 Vornberger, Anton Vorontsov, Daniel Wagner, Phil Xiaojun Hu, Edward
1531 Z. Yang and Norbert Zeh.
15321532
15331533 [jao]: http://jao.io
15341534 [incorporates patches]: http://www.ohloh.net/p/xmobar/contributors
11 -----------------------------------------------------------------------------
22 -- |
33 -- Module : Bitmap
4 -- Copyright : (C) 2013 Alexander Polakov
4 -- Copyright : (C) 2013, 2015 Alexander Polakov
55 -- License : BSD3
66 --
77 -- Maintainer : jao@gnu.org
1515 , drawBitmap
1616 , Bitmap(..)) where
1717
18 import Control.Applicative((<|>))
1918 import Control.Monad
2019 import Control.Monad.Trans(MonadIO(..))
2120 import Data.Map hiding (foldr, map, filter)
2928
3029 #ifdef XPM
3130 import XPMFile(readXPMFile)
31 import Control.Applicative((<|>))
3232 #endif
3333
3434 #if MIN_VERSION_mtl(2, 2, 1)
1818 ) where
1919
2020 import Foreign.C
21 #if ! MIN_VERSION_time(1,5,0)
2122 import qualified System.Locale as L
23 #else
24 import qualified Data.Time.Format as L
25 #endif
2226
2327 #ifdef UTF8
2428 import Codec.Binary.UTF8.String
0 {-# LANGUAGE CPP #-}
01 -----------------------------------------------------------------------------
12 -- |
23 -- Module : Plugins.Date
1920
2021 import Plugins
2122
23 #if ! MIN_VERSION_time(1,5,0)
2224 import System.Locale
25 #endif
2326 import Control.Monad (liftM)
2427 import Data.Time
2528
3030 import System.IO.Unsafe
3131
3232 import Localize
33 import Data.Time.Format
3334 import Data.Time.LocalTime
34 import Data.Time.Format
3535 import Data.Time.LocalTime.TimeZone.Olson
3636 import Data.Time.LocalTime.TimeZone.Series
3737
38 #if ! MIN_VERSION_time(1,5,0)
3839 import System.Locale (TimeLocale)
40 #endif
3941 #else
4042 import System.IO
4143 import Plugins.Date
00 {-# OPTIONS_GHC -w #-}
1 {-# LANGUAGE CPP, NamedFieldPuns, GeneralizedNewtypeDeriving #-}
1 {-# LANGUAGE CPP, NamedFieldPuns, GeneralizedNewtypeDeriving, FlexibleContexts #-}
22
33 -----------------------------------------------------------------------------
44 -- |
1616
1717 module Plugins.EWMH (EWMH(..)) where
1818
19 import Control.Applicative (Applicative(..))
1920 import Control.Monad.State
2021 import Control.Monad.Reader
2122 import Graphics.X11 hiding (Modifier, Color)
175176 , ("_NET_WM_DESKTOP", updateDesktop) ]
176177
177178 newtype M a = M (ReaderT EwmhConf (StateT EwmhState IO) a)
178 deriving (Monad, Functor, MonadIO, MonadReader EwmhConf, MonadState EwmhState)
179 deriving (Monad, Functor, Applicative, MonadIO, MonadReader EwmhConf, MonadState EwmhState)
179180
180181 execM :: M a -> IO a
181182 execM (M m) = do
00 -----------------------------------------------------------------------------
11 -- |
22 -- Module : Plugins.Monitors.Volume
3 -- Copyright : (c) 2011, 2013 Thomas Tuegel
3 -- Copyright : (c) 2011, 2013, 2015 Thomas Tuegel
44 -- License : BSD-style (see LICENSE)
55 --
66 -- Maintainer : Jose A. Ortega Ruiz <jao@gnu.org>
121121 runVolume :: String -> String -> [String] -> Monitor String
122122 runVolume mixerName controlName argv = do
123123 opts <- io $ parseOpts argv
124 (lo, hi, val, db, sw) <- io $ withMixer mixerName $ \mixer -> do
125 control <- getControlByName mixer controlName
126 (lo, hi) <- liftMaybe $ getRange <$> volumeControl control
127 val <- getVal $ volumeControl control
128 db <- getDB $ volumeControl control
129 sw <- getSw $ switchControl control
130 return (lo, hi, val, db, sw)
124 (lo, hi, val, db, sw) <- io readMixer
131125 p <- liftMonitor $ liftM3 formatVol lo hi val
132126 b <- liftMonitor $ liftM3 formatVolBar lo hi val
133127 v <- liftMonitor $ liftM3 formatVolVBar lo hi val
137131 parseTemplate [p, b, v, d, s, ipat]
138132
139133 where
134
135 readMixer =
136 AE.catch (withMixer mixerName $ \mixer -> do
137 control <- getControlByName mixer controlName
138 (lo, hi) <- liftMaybe $ getRange <$> volumeControl control
139 val <- getVal $ volumeControl control
140 db <- getDB $ volumeControl control
141 sw <- getSw $ switchControl control
142 return (lo, hi, val, db, sw))
143 (const $ return (Nothing, Nothing, Nothing, Nothing, Nothing))
140144
141145 volumeControl :: Maybe Control -> Maybe Volume
142146 volumeControl c = join $
153157 liftMonitor Nothing = unavailable
154158 liftMonitor (Just m) = m
155159
160 channel v r = AE.catch (getChannel FrontLeft v) (const $ return $ Just r)
161
156162 getDB :: Maybe Volume -> IO (Maybe Integer)
157163 getDB Nothing = return Nothing
158 getDB (Just v) = AE.catch (getChannel FrontLeft $ dB v)
159 (const $ return $ Just 0)
164 getDB (Just v) = channel (dB v) 0
160165
161166 getVal :: Maybe Volume -> IO (Maybe Integer)
162167 getVal Nothing = return Nothing
163 getVal (Just v) = getChannel FrontLeft $ value v
168 getVal (Just v) = channel (value v) 0
164169
165170 getSw :: Maybe Switch -> IO (Maybe Bool)
166171 getSw Nothing = return Nothing
167 getSw (Just s) = getChannel FrontLeft s
172 getSw (Just s) = channel s False
168173
169174 getFormatDB :: VolumeOpts -> Maybe Integer -> Monitor String
170175 getFormatDB _ Nothing = unavailable
00 -----------------------------------------------------------------------------
11 -- |
22 -- Module : Window
3 -- Copyright : (c) 2011-14 Jose A. Ortega Ruiz
3 -- Copyright : (c) 2011-15 Jose A. Ortega Ruiz
44 -- : (c) 2012 Jochen Keil
55 -- License : BSD-style (see LICENSE)
66 --
170170 TopB -> drawBorder (TopBM 0) lw d p gc c wi ht
171171 BottomB -> drawBorder (BottomBM 0) lw d p gc c wi ht
172172 FullB -> drawBorder (FullBM 0) lw d p gc c wi ht
173 TopBM m -> sf >> sla >> drawLine d p gc 0 (fi m + boff) (fi wi) (fi m + boff)
173 TopBM m -> sf >> sla >>
174 drawLine d p gc 0 (fi m + boff) (fi wi) (fi m + boff)
174175 BottomBM m -> let rw = fi ht - fi m + boff in
175176 sf >> sla >> drawLine d p gc 0 rw (fi wi) rw
176 FullBM m -> let pad = 2 * fi m + 2 * fi boff'; mp = fi m + fi boff' in
177 sf >> sla >> drawRectangle d p gc mp mp (wi - pad) (ht - pad)
177 FullBM m -> let mp = fi m
178 pad = 2 * fi mp + fi lw
179 in sf >> sla >>
180 drawRectangle d p gc mp mp (wi - pad + 1) (ht - pad)
178181 where sf = setForeground d gc c
179182 sla = setLineAttributes d gc (fi lw) lineSolid capNotLast joinMiter
180183 boff = borderOffset b lw
181 boff' = calcBorderOffset lw :: Int
184 -- boff' = calcBorderOffset lw :: Int
182185
183186 hideWindow :: Display -> Window -> IO ()
184187 hideWindow d w = do
208211 calcBorderOffset :: (Integral a) => Int -> a
209212 calcBorderOffset = ceiling . (/2) . toDouble
210213 where toDouble = fi :: (Integral a) => a -> Double
211
183183 when (al == 255) $ do
184184 (a,d) <- textExtents fs s
185185 gi <- xftTxtExtents' dpy fonts s
186 drawXftRect draw bc' (x + 1 - fi (xglyphinfo_x gi))
187 (y - (a + d) + 1) (xglyphinfo_xOff gi) (a + d)
188 (drawXftString' draw fc' fonts (toInteger x) (toInteger (y - 2)) s)
186 drawXftRect draw bc' x (y - a + 1) (xglyphinfo_xOff gi) (a + d + 1)
187 drawXftString' draw fc' fonts (toInteger x) (toInteger y) s
189188 #endif
190189
191190
201201 eventLoop tv xc as signal
202202
203203 reposWindow rcfg = do
204 r' <- repositionWin d w (fs!!0) rcfg
204 r' <- repositionWin d w (head fs) rcfg
205205 eventLoop tv (XConf d r' w fs is rcfg) as signal
206206
207207 updateConfigPosition ocfg =
305305 printStrings p gc fs 1 L =<< strLn left
306306 printStrings p gc fs 1 R =<< strLn right
307307 printStrings p gc fs 1 C =<< strLn center
308 -- draw 1 pixel border if requested
308 -- draw border if requested
309309 io $ drawBorder (border c) (borderWidth c) d p gc bdcolor wid ht
310310 -- copy the pixmap with the new string to the window
311311 io $ copyArea d p w gc 0 0 wid ht 0 0
315315 -- resync
316316 io $ sync d True
317317
318 verticalOffset :: (Integral b, Integral a, MonadIO m) =>
319 a -> Widget -> XFont -> Config -> m b
318 verticalOffset :: (Integral b, Integral a, MonadIO m) =>
319 a -> Widget -> XFont -> Config -> m b
320320 verticalOffset ht (Text t) fontst conf
321321 | textOffset conf > -1 = return $ fi (textOffset conf)
322322 | otherwise = do
323323 (as,ds) <- io $ textExtents fontst t
324 let bwidth = borderOffset (border conf) (borderWidth conf)
325 verticalMargin = fi ht - fi (as + ds) - 2 * fi (abs bwidth)
326 return $ fi ht - fi ds - (verticalMargin `div` 2) + bwidth + 1
327 verticalOffset _ (Icon _) _ conf
324 let margin = (fi ht - fi ds - fi as) `div` 2
325 return $ fi as + margin - 1
326 verticalOffset ht (Icon _) _ conf
328327 | iconOffset conf > -1 = return $ fi (iconOffset conf)
329 | otherwise = do
330 let bwidth = borderOffset (border conf) (borderWidth conf)
331 return $ bwidth + 1
328 | otherwise = return $ fi (ht `div` 2) - 1
332329
333330 -- | An easy way to print the stuff we need to print
334331 printStrings :: Drawable -> GC -> [XFont] -> Position
00 name: xmobar
1 version: 0.23
1 version: 0.23.1
22 homepage: http://xmobar.org
33 synopsis: A Minimalistic Text Based Status Bar
44 description: Xmobar is a minimalistic text based status bar.
127127 cpp-options: -DGHC6
128128
129129 if flag(with_xft) || flag(all_extensions)
130 build-depends: utf8-string == 0.3.*, X11-xft >= 0.2 && < 0.4
130 build-depends: utf8-string >= 0.3 && < 1.1, X11-xft >= 0.2 && < 0.4
131131 other-modules: MinXft
132132 cpp-options: -DXFT
133133
134134 if flag(with_utf8) || flag(all_extensions)
135 build-depends: utf8-string == 0.3.*
135 build-depends: utf8-string >= 0.3 && < 1.1
136136 cpp-options: -DUTF8
137137
138138 if flag(with_inotify) || flag(all_extensions)