diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Batt.hs | 73 | 
1 files changed, 56 insertions, 17 deletions
| diff --git a/src/Xmobar/Plugins/Monitors/Batt.hs b/src/Xmobar/Plugins/Monitors/Batt.hs index 8cd196d..0181f83 100644 --- a/src/Xmobar/Plugins/Monitors/Batt.hs +++ b/src/Xmobar/Plugins/Monitors/Batt.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE CPP #-} +  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Batt @@ -17,11 +19,14 @@ module Xmobar.Plugins.Monitors.Batt ( battConfig, runBatt, runBatt' ) where  import System.Process (system)  import Control.Monad (void, unless) -import Control.Exception (SomeException, handle)  import Xmobar.Plugins.Monitors.Common +import Control.Exception (SomeException, handle)  import System.FilePath ((</>))  import System.IO (IOMode(ReadMode), hGetLine, withFile)  import System.Posix.Files (fileExist) +#ifdef FREEBSD +import System.BSD.Sysctl (sysctlReadInt) +#endif  import System.Console.GetOpt  import Data.List (sort, sortBy, group)  import Data.Maybe (fromMaybe) @@ -104,7 +109,7 @@ options =    ]  data Status = Charging | Discharging | Full | Idle | Unknown deriving (Read, Eq) - +-- Result perc watts time-seconds Status  data Result = Result Float Float Float Status | NA  sysDir :: FilePath @@ -148,6 +153,38 @@ getBattStatus charge opts   where     c = 100 * min 1 charge +maybeAlert :: BattOpts -> Float -> IO () +maybeAlert opts left = +  case onLowAction opts of +    Nothing -> return () +    Just x -> unless (isNaN left || actionThreshold opts < 100 * left) +                $ void $ system x + +-- | FreeBSD battery query +#ifdef FREEBSD +battStatusFbsd :: Int -> Status +battStatusFbsd x +  | x == 1 = Discharging +  | x == 2 = Charging +  | otherwise = Unknown + +readBatteriesFbsd :: BattOpts -> IO Result +readBatteriesFbsd opts = do +  lf <- sysctlReadInt "hw.acpi.battery.life" +  rt <- sysctlReadInt "hw.acpi.battery.rate" +  tm <- sysctlReadInt "hw.acpi.battery.time" +  st <- sysctlReadInt "hw.acpi.battery.state" +  acline <- sysctlReadInt "hw.acpi.acline" +  let sts = battStatusFbsd $ fromIntegral st +      p = fromIntegral lf / 100 +      w = fromIntegral rt +      t = fromIntegral tm * 60 +      ac = acline == 1 +  unless ac (maybeAlert opts p) +  return (Result p w t sts) + +#else +-- | query linux battery  safeFileExist :: String -> String -> IO Bool  safeFileExist d f = handle noErrors $ fileExist (d </> f)    where noErrors = const (return False) :: SomeException -> IO Bool @@ -204,15 +241,8 @@ sortOn f =  mostCommonDef :: Eq a => a -> [a] -> a  mostCommonDef x xs = head $ last $ [x] : sortOn length (group xs) -maybeAlert :: BattOpts -> Float -> IO () -maybeAlert opts left = -  case onLowAction opts of -    Nothing -> return () -    Just x -> unless (isNaN left || actionThreshold opts < 100 * left) -                $ void $ system x - -readBatteries :: BattOpts -> [Files] -> IO Result -readBatteries opts bfs = +readBatteriesLinux :: BattOpts -> [Files] -> IO Result +readBatteriesLinux opts bfs =      do let bfs' = filter (/= NoFiles) bfs         bats <- mapM (readBattery (scale opts)) (take 3 bfs')         ac <- haveAc (onlineFile opts) @@ -233,6 +263,7 @@ readBatteries opts bfs =                   | otherwise = Discharging         unless ac (maybeAlert opts left)         return $ if isNaN left then NA else Result left watts time racst +#endif  runBatt :: [String] -> Monitor String  runBatt = runBatt' ["BAT", "BAT0", "BAT1", "BAT2"] @@ -240,18 +271,26 @@ runBatt = runBatt' ["BAT", "BAT0", "BAT1", "BAT2"]  runBatt' :: [String] -> [String] -> Monitor String  runBatt' bfs args = do    opts <- io $ parseOptsWith options defaultOpts args -  let sp = incPerc opts -  c <- io $ readBatteries opts =<< mapM batteryFiles bfs +#ifdef FREEBSD +  c <- io $ readBatteriesFbsd opts +#else +  c <- io $ readBatteriesLinux opts =<< mapM batteryFiles bfs +#endif +  formatResult c opts + +formatResult :: Result -> BattOpts -> Monitor String +formatResult res bopt = do +  let sp = incPerc bopt    suffix <- getConfigValue useSuffix    d <- getConfigValue decDigits    nas <- getConfigValue naString -  case c of +  case res of      Result x w t s ->        do l <- fmtPercent x sp -         ws <- fmtWatts w opts suffix d -         si <- getIconPattern opts s x +         ws <- fmtWatts w bopt suffix d +         si <- getIconPattern bopt s x           st <- showWithColors' -                 (fmtStatus opts s nas (getBattStatus x opts)) +                 (fmtStatus bopt s nas (getBattStatus x bopt))                   (100 * x)           parseTemplate (l ++ [st, fmtTime $ floor t, ws, si])      NA -> getConfigValue naString | 
