diff options
Diffstat (limited to 'src/Plugins')
-rw-r--r-- | src/Plugins/Monitors/Batt.hs | 69 | ||||
-rw-r--r-- | src/Plugins/Monitors/CoreCommon.hs | 13 |
2 files changed, 48 insertions, 34 deletions
diff --git a/src/Plugins/Monitors/Batt.hs b/src/Plugins/Monitors/Batt.hs index c276e6b..77b2d62 100644 --- a/src/Plugins/Monitors/Batt.hs +++ b/src/Plugins/Monitors/Batt.hs @@ -13,11 +13,14 @@ -- ----------------------------------------------------------------------------- +{-# LANGUAGE BangPatterns #-} + module Plugins.Monitors.Batt ( battConfig, runBatt, runBatt' ) where -import qualified Data.ByteString.Lazy.Char8 as B +import Control.Exception (SomeException, handle) import Plugins.Monitors.Common import System.FilePath ((</>)) +import System.IO (IOMode(ReadMode), hGetLine, withFile) import System.Posix.Files (fileExist) import System.Console.GetOpt @@ -83,17 +86,21 @@ data Files = Files } | NoFiles data Battery = Battery - { full :: Float - , now :: Float - , voltage :: Float - , current :: Float + { full :: !Float + , now :: !Float + , voltage :: !Float + , current :: !Float } +safeFileExist :: String -> IO Bool +safeFileExist f = handle noErrors $ fileExist f + where noErrors = const (return False) :: SomeException -> IO Bool + batteryFiles :: String -> IO Files batteryFiles bat = - do is_charge <- fileExist $ prefix </> "charge_now" - is_energy <- fileExist $ prefix </> "energy_now" - is_current <- fileExist $ prefix </> "current_now" + do is_charge <- safeFileExist $ prefix </> "charge_now" + is_energy <- safeFileExist $ prefix </> "energy_now" + is_current <- safeFileExist $ prefix </> "current_now" let cf = if is_current then "current_now" else "power_now" return $ case (is_charge, is_energy) of (True, _) -> files "charge" cf @@ -106,12 +113,9 @@ batteryFiles bat = , fVoltage = prefix </> "voltage_now" } haveAc :: FilePath -> IO Bool -haveAc f = do - exists <- fileExist ofile - if exists - then fmap ((== "1\n") . B.unpack) (B.readFile ofile) - else return False - where ofile = sysDir </> f +haveAc f = + handle onError $ withFile (sysDir </> f) ReadMode (fmap (== "1") . hGetLine) + where onError = const (return False) :: SomeException -> IO Bool readBattery :: Files -> IO Battery readBattery NoFiles = return $ Battery 0 0 0 0 @@ -124,7 +128,8 @@ readBattery files = (3600 * b / 1000000) -- wattseconds (c / 1000000) -- volts (if c > 0 then (d / c) else -1) -- amperes - where grab f = catch (fmap (read . B.unpack) $ B.readFile f) (\_ -> return 0) + where grab f = handle onError $ withFile f ReadMode (fmap read . hGetLine) + onError = const (return (-1)) :: SomeException -> IO Float readBatteries :: BattOpts -> [Files] -> IO Result readBatteries opts bfs = @@ -152,20 +157,20 @@ runBatt' bfs args = do do l <- fmtPercent x parseTemplate (l ++ s:[fmtTime $ floor t, fmtWatts w opts]) NA -> return "N/A" - where fmtPercent :: Float -> Monitor [String] - fmtPercent x = do - p <- showPercentWithColors x - b <- showPercentBar (100 * x) x - return [b, p] - fmtWatts x o = color x o $ showDigits 1 x ++ "W" - 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) - maybeColor Nothing _ = "" - 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) + where fmtPercent :: Float -> Monitor [String] + fmtPercent x = do + p <- showPercentWithColors x + b <- showPercentBar (100 * x) x + return [b, p] + fmtWatts x o = color x o $ showDigits 1 x ++ "W" + 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) + maybeColor Nothing _ = "" + 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) diff --git a/src/Plugins/Monitors/CoreCommon.hs b/src/Plugins/Monitors/CoreCommon.hs index e508f7d..eb3e17f 100644 --- a/src/Plugins/Monitors/CoreCommon.hs +++ b/src/Plugins/Monitors/CoreCommon.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE PatternGuards, CPP #-} ----------------------------------------------------------------------------- -- | @@ -25,6 +25,15 @@ import Data.Maybe import Plugins.Monitors.Common import System.Directory +#ifdef GHC6 +import Control.Monad.Reader + +instance (Monad f, Applicative f) => Applicative (ReaderT r f) where + pure a = ReaderT $ const (pure a) + f <*> a = ReaderT $ \r -> + ((runReaderT f r) <*> (runReaderT a r)) +#endif + checkedDataRetrieval :: (Ord a, Num a) => String -> [String] -> Maybe (String, String -> Int) -> (Double -> a) -> (a -> String) -> Monitor String @@ -131,4 +140,4 @@ readFiles (fval, flbl) = (,) <$> either return (\(f, ex) -> liftM ex -- | Function that captures if-then-else ifthen :: a -> a -> Bool -> a -ifthen thn els cnd = if cnd then thn else els
\ No newline at end of file +ifthen thn els cnd = if cnd then thn else els |