diff options
Diffstat (limited to 'src/Plugins/Monitors')
| -rw-r--r-- | src/Plugins/Monitors/Batt.hs | 75 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Bright.hs | 52 | ||||
| -rw-r--r-- | src/Plugins/Monitors/CatInt.hs | 25 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Common.hs | 146 | ||||
| -rw-r--r-- | src/Plugins/Monitors/CoreCommon.hs | 14 | ||||
| -rw-r--r-- | src/Plugins/Monitors/CoreTemp.hs | 20 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Cpu.hs | 49 | ||||
| -rw-r--r-- | src/Plugins/Monitors/CpuFreq.hs | 32 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Disk.hs | 109 | ||||
| -rw-r--r-- | src/Plugins/Monitors/MPD.hs | 54 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Mem.hs | 73 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Mpris.hs | 19 | ||||
| -rw-r--r-- | src/Plugins/Monitors/MultiCpu.hs | 70 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Net.hs | 96 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Swap.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Thermal.hs | 13 | ||||
| -rw-r--r-- | src/Plugins/Monitors/ThermalZone.hs | 5 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Top.hs | 11 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Volume.hs | 54 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Weather.hs | 139 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Wireless.hs | 42 | 
21 files changed, 802 insertions, 300 deletions
| diff --git a/src/Plugins/Monitors/Batt.hs b/src/Plugins/Monitors/Batt.hs index 4c0232f..f7b31e4 100644 --- a/src/Plugins/Monitors/Batt.hs +++ b/src/Plugins/Monitors/Batt.hs @@ -34,6 +34,9 @@ data BattOpts = BattOpts    , highThreshold :: Float    , onlineFile :: FilePath    , scale :: Float +  , onIconPattern :: Maybe IconPattern +  , offIconPattern :: Maybe IconPattern +  , idleIconPattern :: Maybe IconPattern    }  defaultOpts :: BattOpts @@ -49,6 +52,9 @@ defaultOpts = BattOpts    , highThreshold = -10    , onlineFile = "AC/online"    , scale = 1e6 +  , onIconPattern = Nothing +  , offIconPattern = Nothing +  , idleIconPattern = Nothing    }  options :: [OptDescr (BattOpts -> BattOpts)] @@ -64,6 +70,12 @@ options =    , Option "H" ["hight"] (ReqArg (\x o -> o { highThreshold = read x }) "") ""    , Option "f" ["online"] (ReqArg (\x o -> o { onlineFile = x }) "") ""    , Option "s" ["scale"] (ReqArg (\x o -> o {scale = read x}) "") "" +  , Option "" ["on-icon-pattern"] (ReqArg (\x o -> +     o { onIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["off-icon-pattern"] (ReqArg (\x o -> +     o { offIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["idle-icon-pattern"] (ReqArg (\x o -> +     o { idleIconPattern = Just $ parseIconPattern x }) "") ""    ]  parseOpts :: [String] -> IO BattOpts @@ -72,7 +84,9 @@ parseOpts argv =      (o, _, []) -> return $ foldr id defaultOpts o      (_, _, errs) -> ioError . userError $ concat errs -data Result = Result Float Float Float String | NA +data Status = Charging | Discharging | Idle + +data Result = Result Float Float Float Status | NA  sysDir :: FilePath  sysDir = "/sys/class/power_supply" @@ -80,13 +94,14 @@ sysDir = "/sys/class/power_supply"  battConfig :: IO MConfig  battConfig = mkMConfig         "Batt: <watts>, <left>% / <timeleft>" -- template -       ["leftbar", "left", "acstatus", "timeleft", "watts"] -- replacements +       ["leftbar", "leftvbar", "left", "acstatus", "timeleft", "watts", "leftipat"] -- replacements  data Files = Files    { fFull :: String    , fNow :: String    , fVoltage :: String    , fCurrent :: String +  , isCurrent :: Bool    } | NoFiles  data Battery = Battery @@ -103,20 +118,21 @@ batteryFiles :: String -> IO Files  batteryFiles bat =    do is_charge <- exists "charge_now"       is_energy <- if is_charge then return False else exists "energy_now" -     is_current <- exists "current_now" -     plain <- if is_charge then exists "charge_full" else exists "energy_full" -     let cf = if is_current then "current_now" else "power_now" +     is_power <- exists "power_now" +     plain <- exists (if is_charge then "charge_full" else "energy_full") +     let cf = if is_power then "power_now" else "current_now"           sf = if plain then "" else "_design"       return $ case (is_charge, is_energy) of -       (True, _) -> files "charge" cf sf -       (_, True) -> files "energy" cf sf +       (True, _) -> files "charge" cf sf is_power +       (_, True) -> files "energy" cf sf is_power         _ -> NoFiles    where prefix = sysDir </> bat          exists = safeFileExist prefix -        files ch cf sf = Files { fFull = prefix </> ch ++ "_full" ++ sf -                               , fNow = prefix </> ch ++ "_now" -                               , fCurrent = prefix </> cf -                               , fVoltage = prefix </> "voltage_now" } +        files ch cf sf ip = Files { fFull = prefix </> ch ++ "_full" ++ sf +                                  , fNow = prefix </> ch ++ "_now" +                                  , fCurrent = prefix </> cf +                                  , fVoltage = prefix </> "voltage_now" +                                  , isCurrent = not ip}  haveAc :: FilePath -> IO Bool  haveAc f = @@ -129,9 +145,10 @@ readBattery sc files =      do a <- grab $ fFull files         b <- grab $ fNow files         d <- grab $ fCurrent files -       return $ Battery (3600 * a / sc) -- wattseconds -                        (3600 * b / sc) -- wattseconds -                        (d / sc) -- watts +       let sc' = if isCurrent files then sc / 10 else sc +       return $ Battery (3600 * a / sc') -- wattseconds +                        (3600 * b / sc') -- wattseconds +                        (d / sc') -- watts      where grab f = handle onError $ withFile f ReadMode (fmap read . hGetLine)            onError = const (return (-1)) :: SomeException -> IO Float @@ -147,9 +164,10 @@ readBatteries opts bfs =             time = if idle then 0 else sum $ map time' bats             mwatts = if idle then 1 else sign * watts             time' b = (if ac then full b - now b else now b) / mwatts -           acstr = if idle then idleString opts else -                     if ac then onString opts else offString opts -       return $ if isNaN left then NA else Result left watts time acstr +           acst | idle      = Idle +                | ac        = Charging +                | otherwise = Discharging +       return $ if isNaN left then NA else Result left watts time acst  runBatt :: [String] -> Monitor String  runBatt = runBatt' ["BAT0","BAT1","BAT2"] @@ -163,24 +181,37 @@ runBatt' bfs args = do    case c of      Result x w t s ->        do l <- fmtPercent x -         let ts = [fmtTime $ floor t, fmtWatts w opts suffix d] -         parseTemplate (l ++ s:ts) -    NA -> return "N/A" +         ws <- fmtWatts w opts suffix d +         si <- getIconPattern opts s x +         parseTemplate (l ++ [fmtStatus opts s, fmtTime $ floor t, ws, si]) +    NA -> getConfigValue naString    where fmtPercent :: Float -> Monitor [String]          fmtPercent x = do            let x' = minimum [1, x]            p <- showPercentWithColors x'            b <- showPercentBar (100 * x') x' -          return [b, p] -        fmtWatts x o s d = color x o $ showDigits d x ++ (if s then "W" else "") +          vb <- showVerticalBar (100 * x') x' +          return [b, vb, p] +        fmtWatts x o s d = do +          ws <- showWithPadding $ showDigits d x ++ (if s then "W" else "") +          return $ color x o ws          fmtTime :: Integer -> String          fmtTime x = hours ++ ":" ++ if length minutes == 2                                      then minutes else '0' : minutes            where hours = show (x `div` 3600)                  minutes = show ((x `mod` 3600) `div` 60) +        fmtStatus opts Idle = idleString opts +        fmtStatus opts Charging = onString opts +        fmtStatus opts Discharging = offString opts          maybeColor Nothing str = str          maybeColor (Just c) str = "<fc=" ++ c ++ ">" ++ str ++ "</fc>"          color x o | x >= 0 = maybeColor (posColor o)                    | -x >= highThreshold o = maybeColor (highWColor o)                    | -x >= lowThreshold o = maybeColor (mediumWColor o)                    | otherwise = maybeColor (lowWColor o) +        getIconPattern opts status x = do +          let x' = minimum [1, x] +          case status of +               Idle -> showIconPattern (idleIconPattern opts) x' +               Charging -> showIconPattern (onIconPattern opts) x' +               Discharging -> showIconPattern (offIconPattern opts) x' diff --git a/src/Plugins/Monitors/Bright.hs b/src/Plugins/Monitors/Bright.hs index 0679ab8..cb510f6 100644 --- a/src/Plugins/Monitors/Bright.hs +++ b/src/Plugins/Monitors/Bright.hs @@ -14,9 +14,9 @@  module Plugins.Monitors.Bright (brightConfig, runBright) where +import Control.Applicative ((<$>))  import Control.Exception (SomeException, handle)  import qualified Data.ByteString.Lazy.Char8 as B -import Data.Char  import System.FilePath ((</>))  import System.Posix.Files (fileExist)  import System.Console.GetOpt @@ -26,18 +26,22 @@ import Plugins.Monitors.Common  data BrightOpts = BrightOpts { subDir :: String                               , currBright :: String                               , maxBright :: String +                             , curBrightIconPattern :: Maybe IconPattern                               }  defaultOpts :: BrightOpts  defaultOpts = BrightOpts { subDir = "acpi_video0"                           , currBright = "actual_brightness"                           , maxBright = "max_brightness" +                         , curBrightIconPattern = Nothing                           }  options :: [OptDescr (BrightOpts -> BrightOpts)]  options = [ Option "D" ["device"] (ReqArg (\x o -> o { subDir = x }) "") ""            , Option "C" ["curr"] (ReqArg (\x o -> o { currBright = x }) "") ""            , Option "M" ["max"] (ReqArg (\x o -> o { maxBright = x }) "") "" +          , Option "" ["brightness-icon-pattern"] (ReqArg (\x o -> +             o { curBrightIconPattern = Just $ parseIconPattern x }) "") ""            ]  -- from Batt.hs @@ -52,7 +56,7 @@ sysDir = "/sys/class/backlight/"  brightConfig :: IO MConfig  brightConfig = mkMConfig "<percent>" -- template -                         ["hbar", "percent", "bar"] -- replacements +                         ["vbar", "percent", "bar", "ipat"] -- replacements  data Files = Files { fCurr :: String                     , fMax :: String @@ -61,12 +65,12 @@ data Files = Files { fCurr :: String  brightFiles :: BrightOpts -> IO Files  brightFiles opts = do -  is_curr <- fileExist $ (fCurr files) -  is_max  <- fileExist $ (fCurr files) -  if is_curr && is_max then return files else return NoFiles -  where prefix = sysDir </> (subDir opts) -        files = Files { fCurr = prefix </> (currBright opts) -                      , fMax = prefix </> (maxBright opts) +  is_curr <- fileExist $ fCurr files +  is_max  <- fileExist $ fCurr files +  return (if is_curr && is_max then files else NoFiles) +  where prefix = sysDir </> subDir opts +        files = Files { fCurr = prefix </> currBright opts +                      , fMax = prefix </> maxBright opts                        }  runBright :: [String] ->  Monitor String @@ -76,30 +80,20 @@ runBright args = do    c <- io $ readBright f    case f of      NoFiles -> return "hurz" -    _ -> fmtPercent c >>= parseTemplate -  where fmtPercent :: Float -> Monitor [String] -        fmtPercent c = do r <- showHorizontalBar (100 * c) -                          s <- showPercentWithColors c -                          t <- showPercentBar (100 * c) c -                          return [r,s,t] +    _ -> fmtPercent opts c >>= parseTemplate +  where fmtPercent :: BrightOpts -> Float -> Monitor [String] +        fmtPercent opts c = do r <- showVerticalBar (100 * c) c +                               s <- showPercentWithColors c +                               t <- showPercentBar (100 * c) c +                               d <- showIconPattern (curBrightIconPattern opts) c +                               return [r,s,t,d]  readBright :: Files -> IO Float  readBright NoFiles = return 0  readBright files = do -  currVal<- grab $ (fCurr files) -  maxVal <- grab $ (fMax files) -  return $ (currVal / maxVal) -  where grab f = handle handler (fmap (read . B.unpack) $ B.readFile f) +  currVal<- grab $ fCurr files +  maxVal <- grab $ fMax files +  return (currVal / maxVal) +  where grab f = handle handler (read . B.unpack <$> B.readFile f)          handler = const (return 0) :: SomeException -> IO Float -showHorizontalBar :: Float -> Monitor String -showHorizontalBar x = do -  return $ [convert x] -  where convert :: Float -> Char -        convert val -          | t <= 9600 = ' ' -          | t > 9608 = chr 9608 -          | otherwise = chr t -          where -            -- we scale from 0 to 100, we have 8 slots (9 elements), 100/8 = 12 -            t = 9600 + ((round val) `div` 12) diff --git a/src/Plugins/Monitors/CatInt.hs b/src/Plugins/Monitors/CatInt.hs new file mode 100644 index 0000000..aacbd71 --- /dev/null +++ b/src/Plugins/Monitors/CatInt.hs @@ -0,0 +1,25 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.CatInt +-- Copyright   :  (c) Nathaniel Wesley Filardo +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Nathaniel Wesley Filardo +-- Stability   :  unstable +-- Portability :  unportable +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.CatInt where + +import Plugins.Monitors.Common +import Plugins.Monitors.CoreCommon + +catIntConfig :: IO MConfig +catIntConfig = mkMConfig "<v>" ["v"] + +runCatInt :: FilePath -> [String] -> Monitor String +runCatInt p _ = +  let failureMessage = "Cannot read: " ++ show p +      fmt x = show (truncate x :: Int) +  in  checkedDataRetrieval failureMessage [[p]] Nothing id fmt diff --git a/src/Plugins/Monitors/Common.hs b/src/Plugins/Monitors/Common.hs index 973c5f9..7d11258 100644 --- a/src/Plugins/Monitors/Common.hs +++ b/src/Plugins/Monitors/Common.hs @@ -23,7 +23,9 @@ module Plugins.Monitors.Common (                         , getConfigValue                         , mkMConfig                         , runM +                       , runMD                         , runMB +                       , runMBD                         , io                         -- * Parsers                         -- $parsers @@ -38,6 +40,8 @@ module Plugins.Monitors.Common (                         , parseTemplate'                         -- ** String Manipulation                         -- $strings +                       , IconPattern +                       , parseIconPattern                         , padString                         , showWithPadding                         , showWithColors @@ -45,7 +49,11 @@ module Plugins.Monitors.Common (                         , showPercentWithColors                         , showPercentsWithColors                         , showPercentBar +                       , showVerticalBar +                       , showIconPattern                         , showLogBar +                       , showLogVBar +                       , showLogIconPattern                         , showWithUnits                         , takeDigits                         , showDigits @@ -56,11 +64,13 @@ module Plugins.Monitors.Common (                         ) where +import Control.Applicative ((<$>))  import Control.Monad.Reader  import qualified Data.ByteString.Lazy.Char8 as B  import Data.IORef  import qualified Data.Map as Map  import Data.List +import Data.Char  import Numeric  import Text.ParserCombinators.Parsec  import System.Console.GetOpt @@ -89,6 +99,7 @@ data MConfig =         , barFore     :: IORef String         , barWidth    :: IORef Int         , useSuffix   :: IORef Bool +       , naString    :: IORef String         }  -- | from 'http:\/\/www.haskell.org\/hawiki\/MonadState' @@ -106,7 +117,7 @@ mods s m =  setConfigValue :: a -> Selector a -> Monitor ()  setConfigValue v s = -       mods s (\_ -> v) +       mods s (const v)  getConfigValue :: Selector a -> Monitor a  getConfigValue = sel @@ -132,7 +143,8 @@ mkMConfig tmpl exprts =         bf <- newIORef "#"         bw <- newIORef 10         up <- newIORef False -       return $ MC nc l lc h hc t e p d mn mx pc pr bb bf bw up +       na <- newIORef "N/A" +       return $ MC nc l lc h hc t e p d mn mx pc pr bb bf bw up na  data Opts = HighColor String            | NormalColor String @@ -151,34 +163,39 @@ data Opts = HighColor String            | BarFore String            | BarWidth String            | UseSuffix String +          | NAString String  options :: [OptDescr Opts]  options =      [ -      Option "H"  ["High"] (ReqArg High "number") "The high threshold" -    , Option "L"  ["Low"] (ReqArg Low "number") "The low threshold" -    , Option "h"  ["high"] (ReqArg HighColor "color number") "Color for the high threshold: ex \"#FF0000\"" -    , Option "n"  ["normal"] (ReqArg NormalColor "color number") "Color for the normal threshold: ex \"#00FF00\"" -    , Option "l"  ["low"] (ReqArg LowColor "color number") "Color for the low threshold: ex \"#0000FF\"" -    , Option "t"  ["template"] (ReqArg Template "output template") "Output template." -    , Option "S"  ["suffix"] (ReqArg UseSuffix "True/False") "Use % to display percents or other suffixes." -    , Option "d"  ["ddigits"] (ReqArg DecDigits "decimal digits") "Number of decimal digits to display." -    , Option "p"  ["ppad"] (ReqArg PercentPad "percent padding") "Minimum percentage width." -    , Option "m"  ["minwidth"] (ReqArg MinWidth "minimum width") "Minimum field width" -    , Option "M"  ["maxwidth"] (ReqArg MaxWidth "maximum width") "Maximum field width" -    , Option "w"  ["width"] (ReqArg Width "fixed width") "Fixed field width" -    , Option "c"  ["padchars"] (ReqArg PadChars "padding chars") "Characters to use for padding" -    , Option "a"  ["align"] (ReqArg PadAlign "padding alignment") "'l' for left padding, 'r' for right" -    , Option "b"  ["bback"] (ReqArg BarBack "bar background") "Characters used to draw bar backgrounds" -    , Option "f"  ["bfore"] (ReqArg BarFore "bar foreground") "Characters used to draw bar foregrounds" -    , Option "W"  ["bwidth"] (ReqArg BarWidth "bar width") "Bar width" +      Option "H" ["High"] (ReqArg High "number") "The high threshold" +    , Option "L" ["Low"] (ReqArg Low "number") "The low threshold" +    , Option "h" ["high"] (ReqArg HighColor "color number") "Color for the high threshold: ex \"#FF0000\"" +    , Option "n" ["normal"] (ReqArg NormalColor "color number") "Color for the normal threshold: ex \"#00FF00\"" +    , Option "l" ["low"] (ReqArg LowColor "color number") "Color for the low threshold: ex \"#0000FF\"" +    , Option "t" ["template"] (ReqArg Template "output template") "Output template." +    , Option "S" ["suffix"] (ReqArg UseSuffix "True/False") "Use % to display percents or other suffixes." +    , Option "d" ["ddigits"] (ReqArg DecDigits "decimal digits") "Number of decimal digits to display." +    , Option "p" ["ppad"] (ReqArg PercentPad "percent padding") "Minimum percentage width." +    , Option "m" ["minwidth"] (ReqArg MinWidth "minimum width") "Minimum field width" +    , Option "M" ["maxwidth"] (ReqArg MaxWidth "maximum width") "Maximum field width" +    , Option "w" ["width"] (ReqArg Width "fixed width") "Fixed field width" +    , Option "c" ["padchars"] (ReqArg PadChars "padding chars") "Characters to use for padding" +    , Option "a" ["align"] (ReqArg PadAlign "padding alignment") "'l' for left padding, 'r' for right" +    , Option "b" ["bback"] (ReqArg BarBack "bar background") "Characters used to draw bar backgrounds" +    , Option "f" ["bfore"] (ReqArg BarFore "bar foreground") "Characters used to draw bar foregrounds" +    , Option "W" ["bwidth"] (ReqArg BarWidth "bar width") "Bar width" +    , Option "x" ["nastring"] (ReqArg NAString "N/A string") "String used when the monitor is not available"      ] -doArgs :: [String] -> ([String] -> Monitor String) -> Monitor String -doArgs args action = +doArgs :: [String] -> ([String] -> Monitor String) -> ([String] -> Monitor Bool) -> Monitor String +doArgs args action detect =      case getOpt Permute options args of        (o, n, [])   -> do doConfigOptions o -                         action n +                         ready <- detect n +                         if ready +                            then action n +                            else return "<Waiting...>"        (_, _, errs) -> return (concat errs)  doConfigOptions :: [Opts] -> Monitor () @@ -205,16 +222,25 @@ doConfigOptions (o:oo) =            BarBack     s -> setConfigValue s barBack            BarFore     s -> setConfigValue s barFore            BarWidth    w -> setConfigValue (nz w) barWidth -          UseSuffix   u -> setConfigValue (bool u) useSuffix) >> next +          UseSuffix   u -> setConfigValue (bool u) useSuffix +          NAString    s -> setConfigValue s naString) >> next  runM :: [String] -> IO MConfig -> ([String] -> Monitor String) -> Int          -> (String -> IO ()) -> IO ()  runM args conf action r = runMB args conf action (tenthSeconds r) -runMB :: [String] -> IO MConfig -> ([String] -> Monitor String) -         -> IO () -> (String -> IO ()) -> IO () -runMB args conf action wait cb = handle (cb . showException) loop -  where ac = doArgs args action +runMD :: [String] -> IO MConfig -> ([String] -> Monitor String) -> Int +        -> ([String] -> Monitor Bool) -> (String -> IO ()) -> IO () +runMD args conf action r = runMBD args conf action (tenthSeconds r) + +runMB :: [String] -> IO MConfig -> ([String] -> Monitor String) -> IO () +        -> (String -> IO ()) -> IO () +runMB args conf action wait = runMBD args conf action wait (\_ -> return True) + +runMBD :: [String] -> IO MConfig -> ([String] -> Monitor String) -> IO () +        -> ([String] -> Monitor Bool) -> (String -> IO ()) -> IO () +runMBD args conf action wait detect cb = handle (cb . showException) loop +  where ac = doArgs args action detect          loop = conf >>= runReaderT ac >>= cb >> wait >> loop  showException :: SomeException -> String @@ -319,13 +345,25 @@ combine :: Map.Map String String -> [(String, String, String)] -> Monitor String  combine _ [] = return []  combine m ((s,ts,ss):xs) =      do next <- combine m xs -       let str = Map.findWithDefault err ts m -           err = "<" ++ ts ++ " not found!>" -       nstr <- parseTemplate' str m -       return $ s ++ (if null nstr then str else nstr) ++ ss ++ next +       str <- case Map.lookup ts m of +         Nothing -> return $ "<" ++ ts ++ ">" +         Just  r -> let f "" = r; f n = n; in f <$> parseTemplate' r m +       return $ s ++ str ++ ss ++ next  -- $strings +type IconPattern = Int -> String + +parseIconPattern :: String -> IconPattern +parseIconPattern path = +    let spl = splitOnPercent path +    in \i -> concat $ intersperse (show i) spl +  where splitOnPercent [] = [[]] +        splitOnPercent ('%':'%':xs) = [] : splitOnPercent xs +        splitOnPercent (x:xs) = +            let rest = splitOnPercent xs +            in (x : head rest) : tail rest +  type Pos = (Int, Int)  takeDigits :: Int -> Float -> Float @@ -431,8 +469,50 @@ showPercentBar v x = do    s <- colorizeString v (take len $ cycle bf)    return $ s ++ take (bw - len) (cycle bb) +showIconPattern :: Maybe IconPattern -> Float -> Monitor String +showIconPattern Nothing _ = return "" +showIconPattern (Just str) x = return $ str $ convert $ 100 * x +  where convert val +          | t <= 0 = 0 +          | t > 8 = 8 +          | otherwise = t +          where t = round val `div` 12 + +showVerticalBar :: Float -> Float -> Monitor String +showVerticalBar v x = colorizeString v [convert $ 100 * x] +  where convert :: Float -> Char +        convert val +          | t <= 9600 = ' ' +          | t > 9608 = chr 9608 +          | otherwise = chr t +          where t = 9600 + (round val `div` 12) +  showLogBar :: Float -> Float -> Monitor String -showLogBar f v = do +showLogBar f v =  +  let intConfig c = fromIntegral `fmap` getConfigValue c +  in do +    h <- intConfig high +    l <- intConfig low +    bw <- intConfig barWidth +    let [ll, hh] = sort [l, h] +        choose x | x == 0.0 = 0 +                 | x <= ll = 1 / bw +                 | otherwise = f + logBase 2 (x / hh) / bw +    showPercentBar v $ choose v + +showLogVBar :: Float -> Float -> Monitor String +showLogVBar f v = do +  h <- fromIntegral `fmap` getConfigValue high +  l <- fromIntegral `fmap` getConfigValue low +  bw <- fromIntegral `fmap` getConfigValue barWidth +  let [ll, hh] = sort [l, h] +      choose x | x == 0.0 = 0 +               | x <= ll = 1 / bw +               | otherwise = f + logBase 2 (x / hh) / bw +  showVerticalBar v $ choose v + +showLogIconPattern :: Maybe IconPattern -> Float -> Float -> Monitor String +showLogIconPattern str f v = do    h <- fromIntegral `fmap` getConfigValue high    l <- fromIntegral `fmap` getConfigValue low    bw <- fromIntegral `fmap` getConfigValue barWidth @@ -440,4 +520,4 @@ showLogBar f v = do        choose x | x == 0.0 = 0                 | x <= ll = 1 / bw                 | otherwise = f + logBase 2 (x / hh) / bw -  showPercentBar v $ choose v +  showIconPattern str $ choose v diff --git a/src/Plugins/Monitors/CoreCommon.hs b/src/Plugins/Monitors/CoreCommon.hs index c7fb7d5..943f491 100644 --- a/src/Plugins/Monitors/CoreCommon.hs +++ b/src/Plugins/Monitors/CoreCommon.hs @@ -26,16 +26,18 @@ import Plugins.Monitors.Common  import System.Directory  checkedDataRetrieval :: (Ord a, Num a) -                     => String -> [String] -> Maybe (String, String -> Int) +                     => String -> [[String]] -> Maybe (String, String -> Int)                       -> (Double -> a) -> (a -> String) -> Monitor String -checkedDataRetrieval msg path lbl trans fmt = liftM (fromMaybe msg) $ -                                              retrieveData path lbl trans fmt +checkedDataRetrieval msg paths lbl trans fmt = +  liftM (fromMaybe msg . listToMaybe . catMaybes) $ +    mapM (\p -> retrieveData p lbl trans fmt) paths  retrieveData :: (Ord a, Num a)               => [String] -> Maybe (String, String -> Int)               -> (Double -> a) -> (a -> String) -> Monitor (Maybe String)  retrieveData path lbl trans fmt = do -  pairs <- map snd . sortBy (compare `on` fst) <$> (mapM readFiles =<< findFiles path lbl) +  pairs <- map snd . sortBy (compare `on` fst) <$> +             (mapM readFiles =<< findFilesAndLabel path lbl)    if null pairs      then return Nothing      else Just <$> (     parseTemplate @@ -84,9 +86,9 @@ pathComponents = joinComps . drop 2 . intercalate [Space] . map splitParts  -- | Function to find all files matching the given path and possible label file.  -- The path must be absolute (start with a leading slash). -findFiles :: [String] -> Maybe (String, String -> Int) +findFilesAndLabel :: [String] -> Maybe (String, String -> Int)            -> Monitor [(String, Either Int (String, String -> Int))] -findFiles path lbl  =  catMaybes +findFilesAndLabel path lbl  =  catMaybes                     <$> (     mapM addLabel . zip [0..] . sort                           =<< recFindFiles (pathComponents path) "/"                         ) diff --git a/src/Plugins/Monitors/CoreTemp.hs b/src/Plugins/Monitors/CoreTemp.hs index 2880751..e19baf0 100644 --- a/src/Plugins/Monitors/CoreTemp.hs +++ b/src/Plugins/Monitors/CoreTemp.hs @@ -27,17 +27,19 @@ import Data.Char (isDigit)  coreTempConfig :: IO MConfig  coreTempConfig = mkMConfig         "Temp: <core0>C" -- template -       (zipWith (++) (repeat "core") (map show [0 :: Int ..])) -- available -                                                               -- replacements +       (map ((++) "core" . show) [0 :: Int ..]) -- available +                                                -- replacements  -- |  -- Function retrieves monitor string holding the core temperature  -- (or temperatures)  runCoreTemp :: [String] -> Monitor String -runCoreTemp _ = let path = ["/sys/bus/platform/devices/coretemp.", -                            "/temp", -                            "_input"] -                    lbl  = Just ("_label", read . (dropWhile (not . isDigit))) -                    divisor = 1e3 :: Double -                    failureMessage = "CoreTemp: N/A" -                in  checkedDataRetrieval failureMessage path lbl (/divisor) show +runCoreTemp _ = do +   dn <- getConfigValue decDigits +   failureMessage <- getConfigValue naString +   let path = ["/sys/bus/platform/devices/coretemp.", "/temp", "_input"] +       path' = ["/sys/bus/platform/devices/coretemp.", "/hwmon/hwmon", "/temp", "_input"] +       lbl  = Just ("_label", read . dropWhile (not . isDigit)) +       divisor = 1e3 :: Double +       show' = showDigits (max 0 dn) +   checkedDataRetrieval failureMessage [path, path'] lbl (/divisor) show' diff --git a/src/Plugins/Monitors/Cpu.hs b/src/Plugins/Monitors/Cpu.hs index 6627f53..7fed989 100644 --- a/src/Plugins/Monitors/Cpu.hs +++ b/src/Plugins/Monitors/Cpu.hs @@ -18,18 +18,40 @@ module Plugins.Monitors.Cpu (startCpu) where  import Plugins.Monitors.Common  import qualified Data.ByteString.Lazy.Char8 as B  import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import System.Console.GetOpt + +data CpuOpts = CpuOpts +  { loadIconPattern :: Maybe IconPattern +  } + +defaultOpts :: CpuOpts +defaultOpts = CpuOpts +  { loadIconPattern = Nothing +  } + +options :: [OptDescr (CpuOpts -> CpuOpts)] +options = +  [ Option "" ["load-icon-pattern"] (ReqArg (\x o -> +     o { loadIconPattern = Just $ parseIconPattern x }) "") "" +  ] + +parseOpts :: [String] -> IO CpuOpts +parseOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs  cpuConfig :: IO MConfig  cpuConfig = mkMConfig         "Cpu: <total>%" -       ["bar","total","user","nice","system","idle","iowait"] +       ["bar","vbar","ipat","total","user","nice","system","idle","iowait"] -type CpuDataRef = IORef [Float] +type CpuDataRef = IORef [Int] -cpuData :: IO [Float] +cpuData :: IO [Int]  cpuData = cpuParser `fmap` B.readFile "/proc/stat" -cpuParser :: B.ByteString -> [Float] +cpuParser :: B.ByteString -> [Int]  cpuParser = map (read . B.unpack) . tail . B.words . head . B.lines  parseCpu :: CpuDataRef -> IO [Float] @@ -38,22 +60,25 @@ parseCpu cref =         b <- cpuData         writeIORef cref b         let dif = zipWith (-) b a -           tot = foldr (+) 0 dif -           percent = map (/ tot) dif +           tot = fromIntegral $ sum dif +           percent = map ((/ tot) . fromIntegral) dif         return percent -formatCpu :: [Float] -> Monitor [String] -formatCpu [] = return $ replicate 6 "" -formatCpu xs = do +formatCpu :: CpuOpts -> [Float] -> Monitor [String] +formatCpu _ [] = return $ replicate 8 "" +formatCpu opts xs = do    let t = sum $ take 3 xs    b <- showPercentBar (100 * t) t +  v <- showVerticalBar (100 * t) t +  d <- showIconPattern (loadIconPattern opts) t    ps <- showPercentsWithColors (t:xs) -  return (b:ps) +  return (b:v:d:ps)  runCpu :: CpuDataRef -> [String] -> Monitor String -runCpu cref _ = +runCpu cref argv =      do c <- io (parseCpu cref) -       l <- formatCpu c +       opts <- io $ parseOpts argv +       l <- formatCpu opts c         parseTemplate l  startCpu :: [String] -> Int -> (String -> IO ()) -> IO () diff --git a/src/Plugins/Monitors/CpuFreq.hs b/src/Plugins/Monitors/CpuFreq.hs index dcf75e5..8301547 100644 --- a/src/Plugins/Monitors/CpuFreq.hs +++ b/src/Plugins/Monitors/CpuFreq.hs @@ -18,22 +18,24 @@ import Plugins.Monitors.Common  import Plugins.Monitors.CoreCommon  -- | --- Cpu frequency default configuration. Default template contains only one --- core frequency, user should specify custom template in order to get more --- cpu frequencies. +-- Cpu frequency default configuration. Default template contains only +-- one core frequency, user should specify custom template in order to +-- get more cpu frequencies.  cpuFreqConfig :: IO MConfig -cpuFreqConfig = mkMConfig -       "Freq: <cpu0>" -- template -       (zipWith (++) (repeat "cpu") (map show [0 :: Int ..])) -- available -                                                              -- replacements +cpuFreqConfig = +  mkMConfig "Freq: <cpu0>" (map ((++) "cpu" . show) [0 :: Int ..]) +  -- | --- Function retrieves monitor string holding the cpu frequency (or frequencies) +-- Function retrieves monitor string holding the cpu frequency (or +-- frequencies)  runCpuFreq :: [String] -> Monitor String -runCpuFreq _ = let path = ["/sys/devices/system/cpu/cpu", "/cpufreq/scaling_cur_freq"] -                   divisor = 1e6 :: Double -                   failureMessage = "CpuFreq: N/A" -                   fmt x | x < 1     = (show (round (x * 1000) :: Integer)) ++ "MHz" -                         | otherwise = (show x) ++ "GHz" -               in  checkedDataRetrieval failureMessage path Nothing (/divisor) fmt - +runCpuFreq _ = do +  suffix <- getConfigValue useSuffix +  let path = ["/sys/devices/system/cpu/cpu", "/cpufreq/scaling_cur_freq"] +      divisor = 1e6 :: Double +      fmt x | x < 1 = show (round (x * 1000) :: Integer) ++ +                      if suffix then "MHz" else "" +            | otherwise = show x ++ if suffix then "GHz" else "" +  failureMessage <- getConfigValue naString +  checkedDataRetrieval failureMessage [path] Nothing (/divisor) fmt diff --git a/src/Plugins/Monitors/Disk.hs b/src/Plugins/Monitors/Disk.hs index 73bd5b7..0019c1a 100644 --- a/src/Plugins/Monitors/Disk.hs +++ b/src/Plugins/Monitors/Disk.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Disk --- Copyright   :  (c) 2010, 2011, 2012 Jose A Ortega Ruiz +-- Copyright   :  (c) 2010, 2011, 2012, 2014 Jose A Ortega Ruiz  -- License     :  BSD-style (see LICENSE)  --  -- Maintainer  :  Jose A Ortega Ruiz <jao@gnu.org> @@ -23,15 +23,69 @@ import Control.Exception (SomeException, handle)  import Control.Monad (zipWithM)  import qualified Data.ByteString.Lazy.Char8 as B  import Data.List (isPrefixOf, find) -import System.Directory (canonicalizePath) +import Data.Maybe (catMaybes) +import System.Directory (canonicalizePath, doesFileExist) +import System.Console.GetOpt + +data DiskIOOpts = DiskIOOpts +  { totalIconPattern :: Maybe IconPattern +  , writeIconPattern :: Maybe IconPattern +  , readIconPattern :: Maybe IconPattern +  } + +parseDiskIOOpts :: [String] -> IO DiskIOOpts +parseDiskIOOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs + where defaultOpts = DiskIOOpts +          { totalIconPattern = Nothing +          , writeIconPattern = Nothing +          , readIconPattern = Nothing +          } +       options = +          [ Option "" ["total-icon-pattern"] (ReqArg (\x o -> +             o { totalIconPattern = Just $ parseIconPattern x}) "") "" +          , Option "" ["write-icon-pattern"] (ReqArg (\x o -> +             o { writeIconPattern = Just $ parseIconPattern x}) "") "" +          , Option "" ["read-icon-pattern"] (ReqArg (\x o -> +             o { readIconPattern = Just $ parseIconPattern x}) "") "" +          ]  diskIOConfig :: IO MConfig -diskIOConfig = mkMConfig "" ["total", "read", "write", -                             "totalbar", "readbar", "writebar"] +diskIOConfig = mkMConfig "" ["total", "read", "write" +                            ,"totalbar", "readbar", "writebar" +                            ,"totalvbar", "readvbar", "writevbar" +                            ,"totalipat", "readipat", "writeipat" +                            ] + +data DiskUOpts = DiskUOpts +  { freeIconPattern :: Maybe IconPattern +  , usedIconPattern :: Maybe IconPattern +  } + +parseDiskUOpts :: [String] -> IO DiskUOpts +parseDiskUOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs + where defaultOpts = DiskUOpts +          { freeIconPattern = Nothing +          , usedIconPattern = Nothing +          } +       options = +          [ Option "" ["free-icon-pattern"] (ReqArg (\x o -> +             o { freeIconPattern = Just $ parseIconPattern x}) "") "" +          , Option "" ["used-icon-pattern"] (ReqArg (\x o -> +             o { usedIconPattern = Just $ parseIconPattern x}) "") "" +          ]  diskUConfig :: IO MConfig  diskUConfig = mkMConfig "" -              ["size", "free", "used", "freep", "usedp", "freebar", "usedbar"] +              [ "size", "free", "used", "freep", "usedp" +              , "freebar", "freevbar", "freeipat" +              , "usedbar", "usedvbar", "usedipat" +              ]  type DevName = String  type Path = String @@ -40,11 +94,15 @@ type DevDataRef = IORef [(DevName, [Float])]  mountedDevices :: [String] -> IO [(DevName, Path)]  mountedDevices req = do    s <- B.readFile "/etc/mtab" -  parse `fmap` mapM canon (devs s) +  parse `fmap` mapM mbcanon (devs s)    where +    mbcanon (d, p) = doesFileExist d >>= \e -> +                     if e +                        then Just `fmap` canon (d,p) +                        else return Nothing      canon (d, p) = do {d' <- canonicalizePath d; return (d', p)}      devs = filter isDev . map (firstTwo . B.words) . B.lines -    parse = map undev . filter isReq +    parse = map undev . filter isReq . catMaybes      firstTwo (a:b:_) = (B.unpack a, B.unpack b)      firstTwo _ = ("", "")      isDev (d, _) = "/dev/" `isPrefixOf` d @@ -56,10 +114,10 @@ diskDevices req = do    s <- B.readFile "/proc/diskstats"    parse `fmap` mapM canon (devs s)    where -    canon (d, p) = do {d' <- canonicalizePath (d); return (d', p)} +    canon (d, p) = do {d' <- canonicalizePath d; return (d', p)}      devs = map (third . B.words) . B.lines      parse = map undev . filter isReq -    third (_:_:c:_) = ("/dev/" ++ (B.unpack c), B.unpack c) +    third (_:_:c:_) = ("/dev/" ++ B.unpack c, B.unpack c)      third _ = ("", "")      isReq (d, p) = p `elem` req || drop 5 d `elem` req      undev (d, f) = (drop 5 d, f) @@ -120,18 +178,22 @@ devTemplates disks mounted dat =                           Nothing -> [0, 0, 0]                           Just (_, xs) -> xs -runDiskIO' :: (String, [Float]) -> Monitor String -runDiskIO' (tmp, xs) = do +runDiskIO' :: DiskIOOpts -> (String, [Float]) -> Monitor String +runDiskIO' opts (tmp, xs) = do    s <- mapM (showWithColors speedToStr) xs    b <- mapM (showLogBar 0.8) xs +  vb <- mapM (showLogVBar 0.8) xs +  ipat <- mapM (\(f,v) -> showLogIconPattern (f opts) 0.8 v) +        $ zip [totalIconPattern, readIconPattern, writeIconPattern] xs    setConfigValue tmp template -  parseTemplate $ s ++ b +  parseTemplate $ s ++ b ++ vb ++ ipat  runDiskIO :: DevDataRef -> [(String, String)] -> [String] -> Monitor String -runDiskIO dref disks _ = do +runDiskIO dref disks argv = do +  opts <- io $ parseDiskIOOpts argv    dev <- io $ mountedOrDiskDevices (map fst disks)    dat <- io $ mountedData dref (map fst dev) -  strs <- mapM runDiskIO' $ devTemplates disks dev dat +  strs <- mapM (runDiskIO' opts) $ devTemplates disks dev dat    return $ unwords strs  startDiskIO :: [(String, String)] -> @@ -152,23 +214,28 @@ fsStats path = do                    used = fsStatBytesUsed f                in return [tot, free, used] -runDiskU' :: String -> String -> Monitor String -runDiskU' tmp path = do +runDiskU' :: DiskUOpts -> String -> String -> Monitor String +runDiskU' opts tmp path = do    setConfigValue tmp template    [total, free, diff] <-  io (handle ign $ fsStats path) -  let strs = map sizeToStr [total, free, diff] +  let strs = map sizeToStr [free, diff]        freep = if total > 0 then free * 100 `div` total else 0        fr = fromIntegral freep / 100 -  s <- zipWithM showWithColors' strs [100, freep, 100 - freep] +  s <- zipWithM showWithColors' strs [freep, 100 - freep]    sp <- showPercentsWithColors [fr, 1 - fr]    fb <- showPercentBar (fromIntegral freep) fr +  fvb <- showVerticalBar (fromIntegral freep) fr +  fipat <- showIconPattern (freeIconPattern opts) fr    ub <- showPercentBar (fromIntegral $ 100 - freep) (1 - fr) -  parseTemplate $ s ++ sp ++ [fb, ub] +  uvb <- showVerticalBar (fromIntegral $ 100 - freep) (1 - fr) +  uipat <- showIconPattern (usedIconPattern opts) (1 - fr) +  parseTemplate $ [sizeToStr total] ++ s ++ sp ++ [fb,fvb,fipat,ub,uvb,uipat]    where ign = const (return [0, 0, 0]) :: SomeException -> IO [Integer]  runDiskU :: [(String, String)] -> [String] -> Monitor String -runDiskU disks _ = do +runDiskU disks argv = do    devs <- io $ mountedDevices (map fst disks) -  strs <- mapM (\(d, p) -> runDiskU' (findTempl d p disks) p) devs +  opts <- io $ parseDiskUOpts argv +  strs <- mapM (\(d, p) -> runDiskU' opts (findTempl d p disks) p) devs    return $ unwords strs diff --git a/src/Plugins/Monitors/MPD.hs b/src/Plugins/Monitors/MPD.hs index 96a8f1d..b54962e 100644 --- a/src/Plugins/Monitors/MPD.hs +++ b/src/Plugins/Monitors/MPD.hs @@ -12,17 +12,19 @@  --  ----------------------------------------------------------------------------- -module Plugins.Monitors.MPD ( mpdConfig, runMPD, mpdWait ) where +module Plugins.Monitors.MPD ( mpdConfig, runMPD, mpdWait, mpdReady ) where  import Data.List +import Data.Maybe (fromMaybe)  import Plugins.Monitors.Common  import System.Console.GetOpt  import qualified Network.MPD as M +import Control.Concurrent (threadDelay)  mpdConfig :: IO MConfig  mpdConfig = mkMConfig "MPD: <state>" -              [ "bar", "state", "statei", "volume", "length" -              , "lapsed", "remaining", "plength", "ppos", "file" +              [ "bar", "vbar", "ipat", "state", "statei", "volume", "length" +              , "lapsed", "remaining", "plength", "ppos", "flags", "file"                , "name", "artist", "composer", "performer"                , "album", "title", "track", "genre"                ] @@ -31,6 +33,7 @@ data MOpts = MOpts    { mPlaying :: String    , mStopped :: String    , mPaused :: String +  , mLapsedIconPattern :: Maybe IconPattern    }  defaultOpts :: MOpts @@ -38,6 +41,7 @@ defaultOpts = MOpts    { mPlaying = ">>"    , mStopped = "><"    , mPaused = "||" +  , mLapsedIconPattern = Nothing    }  options :: [OptDescr (MOpts -> MOpts)] @@ -45,20 +49,35 @@ options =    [ Option "P" ["playing"] (ReqArg (\x o -> o { mPlaying = x }) "") ""    , Option "S" ["stopped"] (ReqArg (\x o -> o { mStopped = x }) "") ""    , Option "Z" ["paused"] (ReqArg (\x o -> o { mPaused = x }) "") "" +  , Option "" ["lapsed-icon-pattern"] (ReqArg (\x o -> +     o { mLapsedIconPattern = Just $ parseIconPattern x }) "") ""    ]  runMPD :: [String] -> Monitor String  runMPD args = do    opts <- io $ mopts args -  let mpd = M.withMPD -  status <- io $ mpd M.status -  song <- io $ mpd M.currentSong +  status <- io $ M.withMPD M.status +  song <- io $ M.withMPD M.currentSong    s <- parseMPD status song opts    parseTemplate s  mpdWait :: IO () -mpdWait = M.withMPD idle >> return () -  where idle = M.idle [M.PlayerS, M.MixerS] +mpdWait = do +  status <- M.withMPD $ M.idle [M.PlayerS, M.MixerS] +  case status of +    Left _ -> threadDelay 10000000 +    _ -> return () + +mpdReady :: [String] -> Monitor Bool +mpdReady _ = do +  response <- io $ M.withMPD M.ping +  case response of +    Right _         -> return True +    -- Only cases where MPD isn't responding is an issue; bogus information at +    -- least won't hold xmobar up. +    Left M.NoMPD    -> return False +    Left (M.ConnectionError _) -> return False +    Left _          -> return True  mopts :: [String] -> IO MOpts  mopts argv = @@ -68,20 +87,23 @@ mopts argv =  parseMPD :: M.Response M.Status -> M.Response (Maybe M.Song) -> MOpts              -> Monitor [String] -parseMPD (Left e) _ _ = return $ show e:repeat "" +parseMPD (Left e) _ _ = return $ show e:replicate 19 ""  parseMPD (Right st) song opts = do    songData <- parseSong song    bar <- showPercentBar (100 * b) b -  return $ [bar, ss, si, vol, len, lap, remain, plen, ppos] ++ songData +  vbar <- showVerticalBar (100 * b) b +  ipat <- showIconPattern (mLapsedIconPattern opts) b +  return $ [bar, vbar, ipat, ss, si, vol, len, lap, remain, plen, ppos, flags] ++ songData    where s = M.stState st          ss = show s          si = stateGlyph s opts -        vol = int2str $ M.stVolume st -        (p, t) = M.stTime st +        vol = int2str $ fromMaybe 0 (M.stVolume st) +        (p, t) = fromMaybe (0, 0) (M.stTime st)          [lap, len, remain] = map showTime [floor p, t, max 0 (t - floor p)]          b = if t > 0 then realToFrac $ p / fromIntegral t else 0          plen = int2str $ M.stPlaylistLength st          ppos = maybe "" (int2str . (+1)) $ M.stSongPos st +        flags = playbackMode st  stateGlyph :: M.State -> MOpts -> String  stateGlyph s o = @@ -90,6 +112,14 @@ stateGlyph s o =      M.Paused -> mPaused o      M.Stopped -> mStopped o +playbackMode :: M.Status -> String +playbackMode s = +  concat [if p s then f else "-" | +          (p,f) <- [(M.stRepeat,"r"), +                    (M.stRandom,"z"), +                    (M.stSingle,"s"), +                    (M.stConsume,"c")]] +  parseSong :: M.Response (Maybe M.Song) -> Monitor [String]  parseSong (Left _) = return $ repeat ""  parseSong (Right Nothing) = return $ repeat "" diff --git a/src/Plugins/Monitors/Mem.hs b/src/Plugins/Monitors/Mem.hs index 3cf46c7..403fa43 100644 --- a/src/Plugins/Monitors/Mem.hs +++ b/src/Plugins/Monitors/Mem.hs @@ -15,12 +15,45 @@  module Plugins.Monitors.Mem (memConfig, runMem, totalMem, usedMem) where  import Plugins.Monitors.Common +import qualified Data.Map as M +import System.Console.GetOpt + +data MemOpts = MemOpts +  { usedIconPattern :: Maybe IconPattern +  , freeIconPattern :: Maybe IconPattern +  , availableIconPattern :: Maybe IconPattern +  } + +defaultOpts :: MemOpts +defaultOpts = MemOpts +  { usedIconPattern = Nothing +  , freeIconPattern = Nothing +  , availableIconPattern = Nothing +  } + +options :: [OptDescr (MemOpts -> MemOpts)] +options = +  [ Option "" ["used-icon-pattern"] (ReqArg (\x o -> +     o { usedIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["free-icon-pattern"] (ReqArg (\x o -> +     o { freeIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["available-icon-pattern"] (ReqArg (\x o -> +     o { availableIconPattern = Just $ parseIconPattern x }) "") "" +  ] + +parseOpts :: [String] -> IO MemOpts +parseOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs  memConfig :: IO MConfig  memConfig = mkMConfig         "Mem: <usedratio>% (<cache>M)" -- template -       ["usedbar", "freebar", "usedratio", "freeratio", "total", -        "free", "buffer", "cache", "rest", "used"] -- available replacements +       ["usedbar", "usedvbar", "usedipat", "freebar", "freevbar", "freeipat", +        "availablebar", "availablevbar", "availableipat", +        "usedratio", "freeratio", "availableratio", +        "total", "free", "buffer", "cache", "available", "used"] -- available replacements  fileMEM :: IO String  fileMEM = readFile "/proc/meminfo" @@ -28,13 +61,15 @@ fileMEM = readFile "/proc/meminfo"  parseMEM :: IO [Float]  parseMEM =      do file <- fileMEM -       let content = map words $ take 4 $ lines file -           [total, free, buffer, cache] = map (\line -> (read $ line !! 1 :: Float) / 1024) content -           rest = free + buffer + cache -           used = total - rest +       let content = map words $ take 8 $ lines file +           info = M.fromList $ map (\line -> (head line, (read $ line !! 1 :: Float) / 1024)) content +           [total, free, buffer, cache] = map (info M.!) ["MemTotal:", "MemFree:", "Buffers:", "Cached:"] +           available = M.findWithDefault (free + buffer + cache) "MemAvailable:" info +           used = total - available             usedratio = used / total             freeratio = free / total -       return [usedratio, freeratio, total, free, buffer, cache, rest, used, freeratio] +           availableratio = available / total +       return [usedratio, freeratio, availableratio, total, free, buffer, cache, available, used]  totalMem :: IO Float  totalMem = fmap ((*1024) . (!!1)) parseMEM @@ -42,20 +77,20 @@ totalMem = fmap ((*1024) . (!!1)) parseMEM  usedMem :: IO Float  usedMem = fmap ((*1024) . (!!6)) parseMEM -formatMem :: [Float] -> Monitor [String] -formatMem (r:fr:xs) = +formatMem :: MemOpts -> [Float] -> Monitor [String] +formatMem opts (r:fr:ar:xs) =      do let f = showDigits 0 -           rr = 100 * r -       ub <- showPercentBar rr r -       fb <- showPercentBar (100 - rr) (1 - r) -       rs <- showPercentWithColors r -       fs <- showPercentWithColors fr -       s <- mapM (showWithColors f) xs -       return (ub:fb:rs:fs:s) -formatMem _ = return $ replicate 10 "N/A" +           mon i x = [showPercentBar (100 * x) x, showVerticalBar (100 * x) x, showIconPattern i x] +       sequence $ mon (usedIconPattern opts) r +           ++ mon (freeIconPattern opts) fr +           ++ mon (availableIconPattern opts) ar +           ++ map showPercentWithColors [r, fr, ar] +           ++ map (showWithColors f) xs +formatMem _ _ = replicate 10 `fmap` getConfigValue naString  runMem :: [String] -> Monitor String -runMem _ = +runMem argv =      do m <- io parseMEM -       l <- formatMem m +       opts <- io $ parseOpts argv +       l <- formatMem opts m         parseTemplate l diff --git a/src/Plugins/Monitors/Mpris.hs b/src/Plugins/Monitors/Mpris.hs index 98b4c0f..245c0df 100644 --- a/src/Plugins/Monitors/Mpris.hs +++ b/src/Plugins/Monitors/Mpris.hs @@ -25,6 +25,7 @@ import Text.Printf (printf)  import DBus  import qualified DBus.Client as DC +import Control.Arrow ((***))  import Data.Maybe ( fromJust )  import Data.Int ( Int32, Int64 )  import System.IO.Unsafe (unsafePerformIO) @@ -43,10 +44,10 @@ instance MprisVersion MprisVersion1 where          { methodCallDestination = Just busName          }          where -        busName       = busName_       $ "org.mpris." ++ p -        objectPath    = objectPath_    $ "/Player" -        interfaceName = interfaceName_ $ "org.freedesktop.MediaPlayer" -        memberName    = memberName_    $ "GetMetadata" +        busName       = busName_     $ "org.mpris." ++ p +        objectPath    = objectPath_    "/Player" +        interfaceName = interfaceName_ "org.freedesktop.MediaPlayer" +        memberName    = memberName_    "GetMetadata"      fieldsList MprisVersion1 = [ "album", "artist", "arturl", "mtime", "title"                                 , "tracknumber" ] @@ -58,10 +59,10 @@ instance MprisVersion MprisVersion2 where          , methodCallBody = arguments          }          where -        busName       = busName_       $ "org.mpris.MediaPlayer2." ++ p -        objectPath    = objectPath_    $ "/org/mpris/MediaPlayer2" -        interfaceName = interfaceName_ $ "org.freedesktop.DBus.Properties" -        memberName    = memberName_    $ "Get" +        busName       = busName_     $ "org.mpris.MediaPlayer2." ++ p +        objectPath    = objectPath_    "/org/mpris/MediaPlayer2" +        interfaceName = interfaceName_ "org.freedesktop.DBus.Properties" +        memberName    = memberName_    "Get"          arguments     = map (toVariant::String -> Variant)                              ["org.mpris.MediaPlayer2.Player", "Metadata"] @@ -98,7 +99,7 @@ fromVar = fromJust . fromVariant  unpackMetadata :: [Variant] -> [(String, Variant)]  unpackMetadata [] = [] -unpackMetadata xs = ((map (\(k, v) -> (fromVar k, fromVar v))) . unpack . head) xs where +unpackMetadata xs = (map (fromVar *** fromVar) . unpack . head) xs where                        unpack v = case variantType v of                              TypeDictionary _ _ -> dictionaryItems $ fromVar v                              TypeVariant -> unpack $ fromVar v diff --git a/src/Plugins/Monitors/MultiCpu.hs b/src/Plugins/Monitors/MultiCpu.hs index a1bb082..eab21da 100644 --- a/src/Plugins/Monitors/MultiCpu.hs +++ b/src/Plugins/Monitors/MultiCpu.hs @@ -15,17 +15,48 @@  module Plugins.Monitors.MultiCpu (startMultiCpu) where  import Plugins.Monitors.Common +import Control.Applicative ((<$>))  import qualified Data.ByteString.Lazy.Char8 as B  import Data.List (isPrefixOf, transpose, unfoldr)  import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import System.Console.GetOpt + +data MultiCpuOpts = MultiCpuOpts +  { loadIconPatterns :: [IconPattern] +  , loadIconPattern :: Maybe IconPattern +  } + +defaultOpts :: MultiCpuOpts +defaultOpts = MultiCpuOpts +  { loadIconPatterns = [] +  , loadIconPattern = Nothing +  } + +options :: [OptDescr (MultiCpuOpts -> MultiCpuOpts)] +options = +  [ Option "" ["load-icon-pattern"] (ReqArg (\x o -> +     o { loadIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["load-icon-patterns"] (ReqArg (\x o -> +     o { loadIconPatterns = parseIconPattern x : loadIconPatterns o }) "") "" +  ] + +parseOpts :: [String] -> IO MultiCpuOpts +parseOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs + +variables :: [String] +variables = ["bar", "vbar","ipat","total","user","nice","system","idle"] +vNum :: Int +vNum = length variables  multiCpuConfig :: IO MConfig  multiCpuConfig =    mkMConfig "Cpu: <total>%" $ -            ["auto" ++ k | k <- monitors] ++ +            ["auto" ++ k | k <- variables] ++              [ k ++ n     | n <- "" : map show [0 :: Int ..] -                         , k <- monitors] -    where monitors = ["bar","total","user","nice","system","idle"] +                         , k <- variables]  type CpuDataRef = IORef [[Float]] @@ -48,34 +79,41 @@ parseCpuData cref =  percent :: [Float] -> [Float] -> [Float]  percent b a = if tot > 0 then map (/ tot) $ take 4 dif else [0, 0, 0, 0]    where dif = zipWith (-) b a -        tot = foldr (+) 0 dif +        tot = sum dif -formatMultiCpus :: [[Float]] -> Monitor [String] -formatMultiCpus [] = return [] -formatMultiCpus xs = fmap concat $ mapM formatCpu xs +formatMultiCpus :: MultiCpuOpts -> [[Float]] -> Monitor [String] +formatMultiCpus _ [] = return [] +formatMultiCpus opts xs = concat <$> mapM (\(i, x) -> formatCpu opts i x) (zip [0..] xs) -formatCpu :: [Float] -> Monitor [String] -formatCpu xs -  | length xs < 4 = showPercentsWithColors $ replicate 6 0.0 -  | otherwise = let t = foldr (+) 0 $ take 3 xs +formatCpu :: MultiCpuOpts -> Int -> [Float] -> Monitor [String] +formatCpu opts i xs +  | length xs < 4 = showPercentsWithColors $ replicate vNum 0.0 +  | otherwise = let t = sum $ take 3 xs                  in do b <- showPercentBar (100 * t) t +                      h <- showVerticalBar (100 * t) t +                      d <- showIconPattern tryString t                        ps <- showPercentsWithColors (t:xs) -                      return (b:ps) +                      return (b:h:d:ps) +  where tryString +          | i == 0 = loadIconPattern opts +          | i <= length (loadIconPatterns opts) = Just $ (loadIconPatterns opts) !! (i - 1) +          | otherwise = Nothing  splitEvery :: (Eq a) => Int -> [a] -> [[a]]  splitEvery n = unfoldr (\x -> if null x then Nothing else Just $ splitAt n x)  groupData :: [String] -> [[String]] -groupData = transpose . tail . splitEvery 6 +groupData = transpose . tail . splitEvery vNum  formatAutoCpus :: [String] -> Monitor [String] -formatAutoCpus [] = return $ replicate 6 "" +formatAutoCpus [] = return $ replicate vNum ""  formatAutoCpus xs = return $ map unwords (groupData xs)  runMultiCpu :: CpuDataRef -> [String] -> Monitor String -runMultiCpu cref _ = +runMultiCpu cref argv =    do c <- io $ parseCpuData cref -     l <- formatMultiCpus c +     opts <- io $ parseOpts argv +     l <- formatMultiCpus opts c       a <- formatAutoCpus l       parseTemplate $ a ++ l diff --git a/src/Plugins/Monitors/Net.hs b/src/Plugins/Monitors/Net.hs index b8adc74..5954a77 100644 --- a/src/Plugins/Monitors/Net.hs +++ b/src/Plugins/Monitors/Net.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Net --- Copyright   :  (c) 2011, 2012 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2011, 2012, 2013, 2014 Jose Antonio Ortega Ruiz  --                (c) 2007-2010 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -22,12 +22,47 @@ import Plugins.Monitors.Common  import Data.IORef (IORef, newIORef, readIORef, writeIORef)  import Data.Time.Clock (UTCTime, getCurrentTime, diffUTCTime) -import Control.Monad (forM, filterM) +import Control.Monad (forM, filterM, liftM)  import System.Directory (getDirectoryContents, doesFileExist)  import System.FilePath ((</>)) +import System.Console.GetOpt  import qualified Data.ByteString.Lazy.Char8 as B +data NetOpts = NetOpts +  { rxIconPattern :: Maybe IconPattern +  , txIconPattern :: Maybe IconPattern +  } + +defaultOpts :: NetOpts +defaultOpts = NetOpts +  { rxIconPattern = Nothing +  , txIconPattern = Nothing +  } + +options :: [OptDescr (NetOpts -> NetOpts)] +options = +  [ Option "" ["rx-icon-pattern"] (ReqArg (\x o -> +     o { rxIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["tx-icon-pattern"] (ReqArg (\x o -> +     o { txIconPattern = Just $ parseIconPattern x }) "") "" +  ] + +parseOpts :: [String] -> IO NetOpts +parseOpts argv = +  case getOpt Permute options argv of +    (o, _, []) -> return $ foldr id defaultOpts o +    (_, _, errs) -> ioError . userError $ concat errs + +data UnitPerSec = Bs | KBs | MBs | GBs deriving (Eq,Enum,Ord) +data NetValue = NetValue Float UnitPerSec deriving (Eq,Show) + +instance Show UnitPerSec where +    show Bs  = "B/s" +    show KBs = "KB/s" +    show MBs = "MB/s" +    show GBs = "GB/s" +  data NetDev = NA              | NI String              | ND String Float Float deriving (Eq,Show,Read) @@ -42,8 +77,8 @@ instance Ord NetDev where      compare NA _               = LT      compare _  NA              = GT      compare (NI _) (NI _)      = EQ -    compare (NI _) (ND _ _ _)  = LT -    compare (ND _ _ _) (NI _)  = GT +    compare (NI _) (ND {})     = LT +    compare (ND {}) (NI _)     = GT      compare (ND _ x1 y1) (ND _ x2 y2) =          if downcmp /= EQ             then downcmp @@ -53,7 +88,7 @@ instance Ord NetDev where  netConfig :: IO MConfig  netConfig = mkMConfig      "<dev>: <rx>KB|<tx>KB"      -- template -    ["dev", "rx", "tx", "rxbar", "txbar"]     -- available replacements +    ["dev", "rx", "tx", "rxbar", "rxvbar", "rxipat", "txbar", "txvbar", "txipat"]     -- available replacements  operstateDir :: String -> FilePath  operstateDir d = "/sys/class/net" </> d </> "operstate" @@ -67,14 +102,14 @@ existingDevs = getDirectoryContents "/sys/class/net" >>= filterM isDev  isUp :: String -> IO Bool  isUp d = do    operstate <- B.readFile (operstateDir d) -  return $ "up" == (B.unpack . head . B.lines) operstate +  return $ (B.unpack . head . B.lines) operstate `elem`  ["up", "unknown"]  readNetDev :: [String] -> IO NetDev  readNetDev (d:x:y:_) = do    up <- isUp d    return (if up then ND d (r x) (r y) else NI d)      where r s | s == "" = 0 -              | otherwise = read s / 1024 +              | otherwise = read s  readNetDev _ = return NA @@ -97,24 +132,28 @@ findNetDev dev = do          isDev (NI d) = d == dev          isDev NA = False -formatNet :: Float -> Monitor (String, String) -formatNet d = do +formatNet :: Maybe IconPattern -> Float -> Monitor (String, String, String, String) +formatNet mipat d = do      s <- getConfigValue useSuffix      dd <- getConfigValue decDigits -    let str = if s then (++"Kb/s") . showDigits dd else showDigits dd +    let str True v = showDigits dd d' ++ show u +            where (NetValue d' u) = byteNetVal v +        str False v = showDigits dd $ v / 1024      b <- showLogBar 0.9 d -    x <- showWithColors str d -    return (x, b) +    vb <- showLogVBar 0.9 d +    ipat <- showLogIconPattern mipat 0.9 d +    x <- showWithColors (str s) d +    return (x, b, vb, ipat) -printNet :: NetDev -> Monitor String -printNet nd = +printNet :: NetOpts -> NetDev -> Monitor String +printNet opts nd =    case nd of      ND d r t -> do -        (rx, rb) <- formatNet r -        (tx, tb) <- formatNet t -        parseTemplate [d,rx,tx,rb,tb] +        (rx, rb, rvb, ripat) <- formatNet (rxIconPattern opts) r +        (tx, tb, tvb, tipat) <- formatNet (txIconPattern opts) t +        parseTemplate [d,rx,tx,rb,rvb,ripat,tb,tvb,tipat]      NI _ -> return "" -    NA -> return "N/A" +    NA -> getConfigValue naString  parseNet :: NetDevRef -> String -> IO NetDev  parseNet nref nd = do @@ -132,14 +171,20 @@ parseNet nref nd = do    return $ diffRate n0 n1  runNet :: NetDevRef -> String -> [String] -> Monitor String -runNet nref i _ = io (parseNet nref i) >>= printNet +runNet nref i argv = do +  dev <- io $ parseNet nref i +  opts <- io $ parseOpts argv +  printNet opts dev  parseNets :: [(NetDevRef, String)] -> IO [NetDev] -parseNets = mapM $ \(ref, i) -> parseNet ref i +parseNets = mapM $ uncurry parseNet  runNets :: [(NetDevRef, String)] -> [String] -> Monitor String -runNets refs _ = io (parseActive refs) >>= printNet -    where parseActive refs' = parseNets refs' >>= return . selectActive +runNets refs argv = do +  dev <- io $ parseActive refs +  opts <- io $ parseOpts argv +  printNet opts dev +    where parseActive refs' = liftM selectActive (parseNets refs')             selectActive = maximum  startNet :: String -> [String] -> Int -> (String -> IO ()) -> IO () @@ -158,3 +203,10 @@ startDynNet a r cb = do              _ <- parseNet nref d              return (nref, d)    runM a netConfig (runNets refs) r cb + +byteNetVal :: Float -> NetValue +byteNetVal v +    | v < 1024**1 = NetValue v Bs +    | v < 1024**2 = NetValue (v/1024**1) KBs +    | v < 1024**3 = NetValue (v/1024**2) MBs +    | otherwise   = NetValue (v/1024**3) GBs diff --git a/src/Plugins/Monitors/Swap.hs b/src/Plugins/Monitors/Swap.hs index 107eb1e..b6c5019 100644 --- a/src/Plugins/Monitors/Swap.hs +++ b/src/Plugins/Monitors/Swap.hs @@ -33,8 +33,8 @@ parseMEM =                 | l /= [] = head l !! i                 | otherwise = B.empty             fs s l -               | l == []    = False -               | otherwise  = head l == B.pack s +               | null l    = False +               | otherwise = head l == B.pack s             get_data s = flip (/) 1024 . read . B.unpack . li 1 . filter (fs s)             st   = map B.words . B.lines $ file             tot  = get_data "SwapTotal:" st diff --git a/src/Plugins/Monitors/Thermal.hs b/src/Plugins/Monitors/Thermal.hs index a3ffe6d..6013511 100644 --- a/src/Plugins/Monitors/Thermal.hs +++ b/src/Plugins/Monitors/Thermal.hs @@ -14,6 +14,7 @@  module Plugins.Monitors.Thermal where +import Control.Monad (liftM)  import qualified Data.ByteString.Lazy.Char8 as B  import Plugins.Monitors.Common  import System.Posix.Files (fileExist) @@ -32,11 +33,9 @@ runThermal args = do      let zone = head args          file = "/proc/acpi/thermal_zone/" ++ zone ++ "/temperature"      exists <- io $ fileExist file -    case exists of -         False  -> return $ "Thermal (" ++ zone ++ "): N/A" -         True   -> do number <- io $ B.readFile file -                                     >>= return . (read :: String -> Int) -                                                . stringParser (1, 0) -                      thermal <- showWithColors show number -                      parseTemplate [  thermal ] +    if exists +        then do number <- io $ liftM ((read :: String -> Int) . stringParser (1, 0)) (B.readFile file) +                thermal <- showWithColors show number +                parseTemplate [  thermal ] +        else return $ "Thermal (" ++ zone ++ "): N/A" diff --git a/src/Plugins/Monitors/ThermalZone.hs b/src/Plugins/Monitors/ThermalZone.hs index 55fb2ca..d692191 100644 --- a/src/Plugins/Monitors/ThermalZone.hs +++ b/src/Plugins/Monitors/ThermalZone.hs @@ -1,7 +1,7 @@  ------------------------------------------------------------------------------  -- |  -- Module       :  Plugins.Monitors.ThermalZone --- Copyright    :  (c) 2011 Jose Antonio Ortega Ruiz +-- Copyright    :  (c) 2011, 2013 Jose Antonio Ortega Ruiz  -- License      :  BSD3-style (see LICENSE)  --  -- Maintainer   :  jao@gnu.org @@ -39,5 +39,4 @@ runThermalZone args = do        then do mdegrees <- io $ B.readFile file >>= parse                temp <- showWithColors show (mdegrees `quot` 1000)                parseTemplate [ temp ] -      else return "N/A" - +      else getConfigValue naString diff --git a/src/Plugins/Monitors/Top.hs b/src/Plugins/Monitors/Top.hs index 6f16bdb..3d246ff 100644 --- a/src/Plugins/Monitors/Top.hs +++ b/src/Plugins/Monitors/Top.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Top --- Copyright   :  (c) Jose A Ortega Ruiz +-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2014 Jose A Ortega Ruiz  -- License     :  BSD-style (see LICENSE)  --  -- Maintainer  :  Jose A Ortega Ruiz <jao@gnu.org> @@ -57,10 +57,15 @@ processes :: IO [FilePath]  processes = fmap (filter isPid) (getDirectoryContents "/proc")    where isPid = (`elem` ['0'..'9']) . head +statWords :: [String] -> [String] +statWords line@(x:pn:ppn:xs) = +  if last pn == ')' then line else statWords (x:(pn ++ " " ++ ppn):xs) +statWords _ = replicate 52 "0" +  getProcessData :: FilePath -> IO [String]  getProcessData pidf =    handle ign $ withFile ("/proc" </> pidf </> "stat") ReadMode readWords -  where readWords = fmap words . hGetLine +  where readWords = fmap (statWords . words) . hGetLine          ign = const (return []) :: SomeException -> IO [String]  handleProcesses :: ([String] -> a) -> IO [a] @@ -96,7 +101,7 @@ meminfos = handleProcesses meminfo  showMemInfo :: Float -> MemInfo -> Monitor [String]  showMemInfo scale (nm, rss) = -  showInfo nm (showWithUnits 2 1 rss) (100 * rss / sc) +  showInfo nm (showWithUnits 3 1 rss) (100 * rss / sc)    where sc = if scale > 0 then scale else 100  showMemInfos :: [MemInfo] -> Monitor [[String]] diff --git a/src/Plugins/Monitors/Volume.hs b/src/Plugins/Monitors/Volume.hs index f3d0f4c..8c39b9f 100644 --- a/src/Plugins/Monitors/Volume.hs +++ b/src/Plugins/Monitors/Volume.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Volume --- Copyright   :  (c) 2011 Thomas Tuegel +-- Copyright   :  (c) 2011, 2013 Thomas Tuegel  -- License     :  BSD-style (see LICENSE)  --  -- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> @@ -24,7 +24,7 @@ import System.Console.GetOpt  volumeConfig :: IO MConfig  volumeConfig = mkMConfig "Vol: <volume>% <status>" -                         ["volume", "volumebar", "dB","status"] +                         ["volume", "volumebar", "volumevbar", "dB","status", "volumeipat"]  data VolumeOpts = VolumeOpts @@ -34,6 +34,7 @@ data VolumeOpts = VolumeOpts      , offColor :: Maybe String      , highDbThresh :: Float      , lowDbThresh :: Float +    , volumeIconPattern :: Maybe IconPattern      }  defaultOpts :: VolumeOpts @@ -44,6 +45,7 @@ defaultOpts = VolumeOpts      , offColor = Just "red"      , highDbThresh = -5.0      , lowDbThresh = -30.0 +    , volumeIconPattern = Nothing      }  options :: [OptDescr (VolumeOpts -> VolumeOpts)] @@ -54,6 +56,8 @@ options =      , Option "" ["highd"] (ReqArg (\x o -> o { highDbThresh = read x }) "") ""      , Option "C" ["onc"] (ReqArg (\x o -> o { onColor = Just x }) "") ""      , Option "c" ["offc"] (ReqArg (\x o -> o { offColor = Just x }) "") "" +    , Option "" ["volume-icon-pattern"] (ReqArg (\x o -> +       o { volumeIconPattern = Just $ parseIconPattern x }) "") ""      ]  parseOpts :: [String] -> IO VolumeOpts @@ -76,6 +80,14 @@ formatVolBar :: Integer -> Integer -> Integer -> Monitor String  formatVolBar lo hi v =      showPercentBar (100 * x) x where x = percent v lo hi +formatVolVBar :: Integer -> Integer -> Integer -> Monitor String +formatVolVBar lo hi v = +    showVerticalBar (100 * x) x where x = percent v lo hi + +formatVolDStr :: Maybe IconPattern -> Integer -> Integer -> Integer -> Monitor String +formatVolDStr ipat lo hi v = +    showIconPattern ipat $ percent v lo hi +  switchHelper :: VolumeOpts               -> (VolumeOpts -> Maybe String)               -> (VolumeOpts -> String) @@ -110,16 +122,20 @@ formatDb opts dbi = do  runVolume :: String -> String -> [String] -> Monitor String  runVolume mixerName controlName argv = do      opts <- io $ parseOpts argv -    control <- io $ getControlByName mixerName controlName -    (lo, hi) <- io . liftMaybe $ getRange <$> volumeControl control -    val <- getVal $ volumeControl control -    db <- getDB $ volumeControl control -    sw <- getSw $ switchControl control +    (lo, hi, val, db, sw) <- io $ withMixer mixerName $ \mixer -> do +        control <- getControlByName mixer controlName +        (lo, hi) <- liftMaybe $ getRange <$> volumeControl control +        val <- getVal $ volumeControl control +        db <- getDB $ volumeControl control +        sw <- getSw $ switchControl control +        return (lo, hi, val, db, sw)      p <- liftMonitor $ liftM3 formatVol lo hi val      b <- liftMonitor $ liftM3 formatVolBar lo hi val +    v <- liftMonitor $ liftM3 formatVolVBar lo hi val      d <- getFormatDB opts db      s <- getFormatSwitch opts sw -    parseTemplate [p, b, d, s] +    ipat <- liftMonitor $ liftM3 (formatVolDStr $ volumeIconPattern opts) lo hi val +    parseTemplate [p, b, v, d, s, ipat]    where @@ -135,28 +151,28 @@ runVolume mixerName controlName argv = do      liftMaybe = fmap (liftM2 (,) (fmap fst) (fmap snd)) . sequenceA      liftMonitor :: Maybe (Monitor String) -> Monitor String -    liftMonitor Nothing = return unavailable +    liftMonitor Nothing = unavailable      liftMonitor (Just m) = m -    getDB :: Maybe Volume -> Monitor (Maybe Integer) +    getDB :: Maybe Volume -> IO (Maybe Integer)      getDB Nothing = return Nothing -    getDB (Just v) = io $ AE.catch (getChannel FrontLeft $ dB v) -                                   (const $ return $ Just 0) +    getDB (Just v) = AE.catch (getChannel FrontLeft $ dB v) +                              (const $ return $ Just 0) -    getVal :: Maybe Volume -> Monitor (Maybe Integer) +    getVal :: Maybe Volume -> IO (Maybe Integer)      getVal Nothing = return Nothing -    getVal (Just v) = io $ getChannel FrontLeft $ value v +    getVal (Just v) = getChannel FrontLeft $ value v -    getSw :: Maybe Switch -> Monitor (Maybe Bool) +    getSw :: Maybe Switch -> IO (Maybe Bool)      getSw Nothing = return Nothing -    getSw (Just s) = io $ getChannel FrontLeft s +    getSw (Just s) = getChannel FrontLeft s      getFormatDB :: VolumeOpts -> Maybe Integer -> Monitor String -    getFormatDB _ Nothing = return unavailable +    getFormatDB _ Nothing = unavailable      getFormatDB opts (Just d) = formatDb opts d      getFormatSwitch :: VolumeOpts -> Maybe Bool -> Monitor String -    getFormatSwitch _ Nothing = return unavailable +    getFormatSwitch _ Nothing = unavailable      getFormatSwitch opts (Just sw) = formatSwitch opts sw -    unavailable = "N/A" +    unavailable = getConfigValue naString diff --git a/src/Plugins/Monitors/Weather.hs b/src/Plugins/Monitors/Weather.hs index 1277438..3cfbc74 100644 --- a/src/Plugins/Monitors/Weather.hs +++ b/src/Plugins/Monitors/Weather.hs @@ -16,13 +16,11 @@ module Plugins.Monitors.Weather where  import Plugins.Monitors.Common -import Control.Monad (when) -import System.Process -import System.Exit -import System.IO +import qualified Control.Exception as CE -import Text.ParserCombinators.Parsec +import Network.HTTP +import Text.ParserCombinators.Parsec  weatherConfig :: IO MConfig  weatherConfig = mkMConfig @@ -33,12 +31,16 @@ weatherConfig = mkMConfig         , "month"         , "day"         , "hour" -       , "wind" +       , "windCardinal" +       , "windAzimuth" +       , "windMph" +       , "windKnots"         , "visibility"         , "skyCondition"         , "tempC"         , "tempF" -       , "dewPoint" +       , "dewPointC" +       , "dewPointF"         , "rh"         , "pressure"         ] @@ -50,12 +52,16 @@ data WeatherInfo =         , month        :: String         , day          :: String         , hour         :: String -       , wind         :: String +       , windCardinal :: String +       , windAzimuth  :: String +       , windMph      :: String +       , windKnots    :: String         , visibility   :: String         , skyCondition :: String         , tempC        :: Int         , tempF        :: Int -       , dewPoint     :: String +       , dewPointC    :: Int +       , dewPointF    :: Int         , humidity     :: Int         , pressure     :: Int         } deriving (Show) @@ -69,7 +75,41 @@ pTime = do y <- getNumbersAsString             char ' '             (h:hh:mi:mimi) <- getNumbersAsString             char ' ' -           return (y, m, d ,([h]++[hh]++":"++[mi]++mimi)) +           return (y, m, d ,h:hh:":"++mi:mimi) + +-- Occasionally there is no wind and a METAR report gives simply, "Wind: Calm:0" +pWind0 :: +  ( +    String -- cardinal direction +  , String -- azimuth direction +  , String -- speed (MPH) +  , String -- speed (knot) +  )        +pWind0 = +  ("μ", "μ", "0", "0") + +pWind :: +  Parser ( +    String -- cardinal direction +  , String -- azimuth direction +  , String -- speed (MPH) +  , String -- speed (knot) +  )        +pWind = +  let tospace = manyTill anyChar (char ' ') +      wind0 = do manyTill skipRestOfLine (string "Wind: Calm:0") +                 return pWind0 +      wind = do manyTill skipRestOfLine (string "Wind: from the ") +                cardinal <- tospace +                char '(' +                azimuth <- tospace +                string "degrees) at " +                mph <- tospace +                string "MPH (" +                knot <- tospace +                manyTill anyChar newline +                return (cardinal, azimuth, mph, knot) +  in try wind0 <|> wind  pTemp :: Parser (Int, Int)  pTemp = do let num = digit <|> char '-' <|> char '.' @@ -77,10 +117,10 @@ pTemp = do let num = digit <|> char '-' <|> char '.'             manyTill anyChar $ char '('             c <- manyTill num $ char ' '             skipRestOfLine -           return $ (floor (read c :: Double), floor (read f :: Double)) +           return (floor (read c :: Double), floor (read f :: Double))  pRh :: Parser Int -pRh = do s <- manyTill digit $ (char '%' <|> char '.') +pRh = do s <- manyTill digit (char '%' <|> char '.')           return $ read s  pPressure :: Parser Int @@ -89,53 +129,84 @@ pPressure = do manyTill anyChar $ char '('                 skipRestOfLine                 return $ read s +{- +    example of 'http://weather.noaa.gov/pub/data/observations/metar/decoded/VTUD.TXT': +        Station name not available +        Aug 11, 2013 - 10:00 AM EDT / 2013.08.11 1400 UTC +        Wind: from the N (350 degrees) at 1 MPH (1 KT):0 +        Visibility: 4 mile(s):0 +        Sky conditions: mostly clear +        Temperature: 77 F (25 C) +        Dew Point: 73 F (23 C) +        Relative Humidity: 88% +        Pressure (altimeter): 29.77 in. Hg (1008 hPa) +        ob: VTUD 111400Z 35001KT 8000 FEW030 25/23 Q1008 A2977 INFO R RWY30 +        cycle: 14 +-}  parseData :: Parser [WeatherInfo]  parseData = -    do st <- getAllBut "," -       space -       ss <- getAllBut "(" +    do (st, ss) <- try (string "Station name not available" >> return ("??", "??")) <|> +                   (do st <- getAllBut "," +                       space +                       ss <- getAllBut "(" +                       return (st, ss) +                   )         skipRestOfLine >> getAllBut "/"         (y,m,d,h) <- pTime -       w <- getAfterString "Wind: " +       (wc, wa, wm, wk) <- pWind         v <- getAfterString "Visibility: "         sk <- getAfterString "Sky conditions: "         skipTillString "Temperature: "         (tC,tF) <- pTemp -       dp <- getAfterString "Dew Point: " +       skipTillString "Dew Point: " +       (dC, dF) <- pTemp         skipTillString "Relative Humidity: "         rh <- pRh         skipTillString "Pressure (altimeter): "         p <- pPressure         manyTill skipRestOfLine eof -       return $ [WI st ss y m d h w v sk tC tF dp rh p] +       return [WI st ss y m d h wc wa wm wk v sk tC tF dC dF rh p]  defUrl :: String  defUrl = "http://weather.noaa.gov/pub/data/observations/metar/decoded/" +stationUrl :: String -> String +stationUrl station = defUrl ++ station ++ ".TXT" +  getData :: String -> IO String -getData url= -        do (i,o,e,p) <- runInteractiveCommand ("curl " ++ defUrl ++ url ++ ".TXT") -           exit <- waitForProcess p -           let closeHandles = do hClose o -                                 hClose i -                                 hClose e -           case exit of -             ExitSuccess -> do str <- hGetContents o -                               when (str == str) $ return () -                               closeHandles -                               return str -             _ -> do closeHandles -                     return "Could not retrieve data" +getData station = do +    let request = getRequest (stationUrl station) +    CE.catch (simpleHTTP request >>= getResponseBody) errHandler +    where errHandler :: CE.IOException -> IO String +          errHandler _ = return "<Could not retrieve data>"  formatWeather :: [WeatherInfo] -> Monitor String -formatWeather [(WI st ss y m d h w v sk tC tF dp r p)] = +formatWeather [WI st ss y m d h wc wa wm wk v sk tC tF dC dF r p] =      do cel <- showWithColors show tC         far <- showWithColors show tF -       parseTemplate [st, ss, y, m, d, h, w, v, sk, cel, far, dp, show r , show p ] -formatWeather _ = return "N/A" +       parseTemplate [st, ss, y, m, d, h, wc, wa, wm, wk, v, sk, cel, far, show dC, show dF, show r , show p ] +formatWeather _ = getConfigValue naString  runWeather :: [String] -> Monitor String  runWeather str =      do d <- io $ getData $ head str         i <- io $ runP parseData d         formatWeather i + +weatherReady :: [String] -> Monitor Bool +weatherReady str = do +    let station = head str +        request = headRequest (stationUrl station) +    io $ CE.catch (simpleHTTP request >>= checkResult) errHandler +    where errHandler :: CE.IOException -> IO Bool +          errHandler _ = return False +          checkResult result = +            case result of +                Left _ -> return False +                Right response -> +                    case rspCode response of +                        -- Permission or network errors are failures; anything +                        -- else is recoverable. +                        (4, _, _) -> return False +                        (5, _, _) -> return False +                        (_, _, _) -> return True diff --git a/src/Plugins/Monitors/Wireless.hs b/src/Plugins/Monitors/Wireless.hs index 8d32c99..b1e3c7e 100644 --- a/src/Plugins/Monitors/Wireless.hs +++ b/src/Plugins/Monitors/Wireless.hs @@ -14,21 +14,49 @@  module Plugins.Monitors.Wireless (wirelessConfig, runWireless)  where +import System.Console.GetOpt +  import Plugins.Monitors.Common  import IWlib +data WirelessOpts = WirelessOpts +  { qualityIconPattern :: Maybe IconPattern +  } + +defaultOpts :: WirelessOpts +defaultOpts = WirelessOpts +  { qualityIconPattern = Nothing +  } + +options :: [OptDescr (WirelessOpts -> WirelessOpts)] +options = +  [ Option "" ["quality-icon-pattern"] (ReqArg (\d opts -> +     opts { qualityIconPattern = Just $ parseIconPattern d }) "") "" +  ] + +parseOpts :: [String] -> IO WirelessOpts +parseOpts argv = +  case getOpt Permute options argv of +       (o, _, []) -> return $ foldr id defaultOpts o +       (_, _, errs) -> ioError . userError $ concat errs +  wirelessConfig :: IO MConfig  wirelessConfig = -  mkMConfig "<essid> <quality>" ["essid", "quality", "qualitybar"] +  mkMConfig "<essid> <quality>" ["essid", "quality", "qualitybar", "qualityvbar", "qualityipat"] -runWireless :: [String] -> Monitor String -runWireless (iface:_) = do +runWireless :: String -> [String] -> Monitor String +runWireless iface args = do +  opts <- io $ parseOpts args    wi <- io $ getWirelessInfo iface +  na <- getConfigValue naString    let essid = wiEssid wi        qlty = fromIntegral $ wiQuality wi -      e = if essid == "" then "N/A" else essid +      e = if essid == "" then na else essid    ep <- showWithPadding e -  q <- if qlty >= 0 then showPercentWithColors (qlty/100) else showWithPadding "" +  q <- if qlty >= 0 +       then showPercentWithColors (qlty / 100) +       else showWithPadding ""    qb <- showPercentBar qlty (qlty / 100) -  parseTemplate [ep, q, qb] -runWireless _ = return "" +  qvb <- showVerticalBar qlty (qlty / 100) +  qipat <- showIconPattern (qualityIconPattern opts) (qlty / 100) +  parseTemplate [ep, q, qb, qvb, qipat] | 
