summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorJose Antonio Ortega Ruiz <jao@gnu.org>2010-12-08 20:41:38 +0100
committerJose Antonio Ortega Ruiz <jao@gnu.org>2010-12-08 20:41:38 +0100
commit18e63c958a0aeeab1e9a3845f813be29bb6c2dec (patch)
tree231580f5592f0df50b6cda93a7f9653fddfffc67
parent5a8064c2a5dd10fb1a6c6c2bf9fa560402f886ac (diff)
downloadxmobar-18e63c958a0aeeab1e9a3845f813be29bb6c2dec.tar.gz
xmobar-18e63c958a0aeeab1e9a3845f813be29bb6c2dec.tar.bz2
Battery monitor: watts and time left (Petr Rockai)
-rw-r--r--Plugins/Monitors/Batt.hs115
1 files changed, 72 insertions, 43 deletions
diff --git a/Plugins/Monitors/Batt.hs b/Plugins/Monitors/Batt.hs
index 547dd02..bb2027c 100644
--- a/Plugins/Monitors/Batt.hs
+++ b/Plugins/Monitors/Batt.hs
@@ -12,67 +12,96 @@
--
-----------------------------------------------------------------------------
-module Plugins.Monitors.Batt where
+module Plugins.Monitors.Batt ( battConfig, runBatt, runBatt' ) where
import qualified Data.ByteString.Lazy.Char8 as B
import Plugins.Monitors.Common
import System.Posix.Files (fileExist)
-data Batt = Batt Float String
- | NA
+data Result = Result { percent :: Float, watts :: Float, time :: Float, ac :: String }
+ | NA
+
+base = "/sys/class/power_supply"
battConfig :: IO MConfig
battConfig = mkMConfig
- "Batt: <left>%" -- template
- ["leftbar", "left", "status"] -- available replacements
+ "Batt: <watts>, <left> / <timeleft>" -- template
+ ["leftbar", "left", "status", "timeleft", "watts"] -- available replacements
-type File = (String, String)
+data Files = Files { f_full :: String, f_now :: String
+ , f_voltage :: String, f_current :: String } | NoFiles
+data Battery = Battery { full :: Float, now :: Float, voltage :: Float, current :: Float }
-file2batfile :: String -> (File, File)
-file2batfile s = ( (s' ++ "/charge_full", s' ++ "/energy_full")
- , (s' ++ "/charge_now" , s' ++ "/energy_now" )
- )
- where s' = "/sys/class/power_supply/" ++ s
+batteryFiles :: String -> IO Files
+batteryFiles bat =
+ do is_charge <- fileExist $ prefix ++ "/charge_now"
+ is_energy <- fileExist $ prefix ++ "/energy_now"
+ return $ case (is_charge, is_energy) of
+ (True, _) -> files "/charge"
+ (_, True) -> files "/energy"
+ _ -> NoFiles
+ where prefix = base ++ "/" ++ bat
+ files ch = Files { f_full = prefix ++ ch ++ "_full"
+ , f_now = prefix ++ ch ++ "_now"
+ , f_current = prefix ++ "/current_now"
+ , f_voltage = prefix ++ "/voltage_now" }
-readFileBatt :: (File, File) -> IO (String, String, String)
-readFileBatt (f,n) =
- do a <- rf f
- b <- rf n
- ac <- fileExist "/sys/class/power_supply/AC0/online"
- c <- if not ac
- then return []
- else do s <- B.unpack `fmap` catRead "/sys/class/power_supply/AC0/online"
- return $ if s == "1\n" then "<fc=green>On</fc>" else"<fc=red>Off</fc>"
- return (a,b,c)
- where rf file = do
- fe <- fileExist (fst file)
- if fe
- then B.unpack `fmap` catRead (fst file)
- else do fe' <- fileExist (snd file)
- if fe'
- then B.unpack `fmap` catRead (snd file)
- else return []
+haveAc :: IO (Maybe Bool)
+haveAc = do know <- fileExist $ base ++ "/AC/online"
+ if know
+ then do s <- B.unpack `fmap` catRead (base ++ "/AC/online")
+ return $ Just $ s == "1\n"
+ else return Nothing
-parseBATT :: [(File,File)] -> IO Batt
-parseBATT bfs =
- do [(a0,b0,c0),(a1,b1,_),(a2,b2,_)] <- mapM readFileBatt (take 3 $ bfs ++ repeat (("",""),("","")))
- let read' s = if s == [] then 0 else read s
- left = (read' b0 + read' b1 + read' b2) / (read' a0 + read' a1 + read' a2) --present / full
- return $ if isNaN left then NA else Batt left c0
+readBattery :: Files -> IO Battery
+readBattery NoFiles = return $ Battery 0 0 0 0
+readBattery files =
+ do a <- grab $ f_full files -- microwatthours
+ b <- grab $ f_now files
+ c <- grab $ f_voltage files -- microvolts
+ d <- grab $ f_current files -- microwatts (huh!)
+ return $ Battery (3600 * a / 1000000) -- wattseconds
+ (3600 * b / 1000000) -- wattseconds
+ (c / 1000000) -- volts
+ (d / c) -- amperes
+ where grab = fmap (read . B.unpack) . catRead
-formatBatt :: Float -> Monitor [String]
-formatBatt x = do
- p <- showPercentsWithColors [x]
- b <- showPercentBar (100 * x) x
- return (b:p)
+readBatteries :: [Files] -> IO Result
+readBatteries bfs =
+ do bats <- mapM readBattery (take 3 bfs)
+ ac' <- haveAc
+ let ac = if ac' == Just True then True else False
+ sign = if ac then 1 else -1
+ left = (sum $ map now bats) / (sum $ map full bats)
+ watts = sign * (sum $ map voltage bats) * (sum $ map current bats)
+ time = if watts == 0 then 0 else sum $ map time' bats -- negate sign
+ time' b = (if ac then full b - now b else now b) / (sign * watts)
+ acstr = case ac' of
+ Nothing -> "?"
+ Just True -> "<fc=green>On</fc>"
+ Just False -> "<fc=red>Off</fc>"
+ return $ if isNaN left then NA else Result left watts time acstr
runBatt :: [String] -> Monitor String
runBatt = runBatt' ["BAT0","BAT1","BAT2"]
runBatt' :: [String] -> [String] -> Monitor String
runBatt' bfs _ = do
- c <- io $ parseBATT (map file2batfile bfs)
+ c <- io $ readBatteries =<< mapM batteryFiles bfs
case c of
- Batt x s -> do l <- formatBatt x
- parseTemplate (l ++ [s])
+ Result x w t s -> do l <- fmtPercent x
+ parseTemplate (l ++ [s] ++ [fmtTime $ floor t, fmtWatts w])
NA -> return "N/A"
+ where fmtPercent :: Float -> Monitor [String]
+ fmtPercent x = do
+ p <- showPercentsWithColors [x]
+ b <- showPercentBar (100 * x) x
+ return (b:p)
+ fmtWatts x = color x $ showDigits 1 x ++ "W"
+ 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)
+ color x str | x >= 0 = "<fc=orange>" ++ str ++ "</fc>"
+ | x >= -10 = "<fc=green>" ++ str ++ "</fc>"
+ | x >= -12 = str
+ | otherwise = "<fc=red>" ++ str ++ "</fc>"