{-# LANGUAGE CPP #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Plugins.Monitors.Batt
-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2015, 2016, 2018, 2019 Jose A Ortega
--                (c) 2010 Andrea Rossato, Petr Rockai
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org>
-- Stability   :  unstable
-- Portability :  unportable
--
-- A battery monitor for Xmobar
--
-----------------------------------------------------------------------------

module Xmobar.Plugins.Monitors.Batt ( battConfig, runBatt, runBatt' ) where

import System.Process (system)
import Control.Monad (void, unless)
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)
import Data.Ord (comparing)
import Text.Read (readMaybe)

data BattOpts = BattOpts
  { BattOpts -> String
onString :: String
  , BattOpts -> String
offString :: String
  , BattOpts -> String
idleString :: String
  , BattOpts -> Maybe String
posColor :: Maybe String
  , BattOpts -> Maybe String
lowWColor :: Maybe String
  , BattOpts -> Maybe String
mediumWColor :: Maybe String
  , BattOpts -> Maybe String
highWColor :: Maybe String
  , BattOpts -> Float
lowThreshold :: Float
  , BattOpts -> Float
highThreshold :: Float
  , BattOpts -> Maybe String
onLowAction :: Maybe String
  , BattOpts -> Float
actionThreshold :: Float
  , BattOpts -> String
onlineFile :: FilePath
  , BattOpts -> Float
scale :: Float
  , BattOpts -> Maybe IconPattern
onIconPattern :: Maybe IconPattern
  , BattOpts -> Maybe IconPattern
offIconPattern :: Maybe IconPattern
  , BattOpts -> Maybe IconPattern
idleIconPattern :: Maybe IconPattern
  , BattOpts -> String
lowString :: String
  , BattOpts -> String
mediumString :: String
  , BattOpts -> String
highString :: String
  , BattOpts -> Bool
incPerc :: Bool
  }

defaultOpts :: BattOpts
defaultOpts :: BattOpts
defaultOpts = BattOpts :: String
-> String
-> String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Float
-> Float
-> Maybe String
-> Float
-> String
-> Float
-> Maybe IconPattern
-> Maybe IconPattern
-> Maybe IconPattern
-> String
-> String
-> String
-> Bool
-> BattOpts
BattOpts
  { onString :: String
onString = String
"On"
  , offString :: String
offString = String
"Off"
  , idleString :: String
idleString = String
"On"
  , posColor :: Maybe String
posColor = Maybe String
forall a. Maybe a
Nothing
  , lowWColor :: Maybe String
lowWColor = Maybe String
forall a. Maybe a
Nothing
  , mediumWColor :: Maybe String
mediumWColor = Maybe String
forall a. Maybe a
Nothing
  , highWColor :: Maybe String
highWColor = Maybe String
forall a. Maybe a
Nothing
  , onLowAction :: Maybe String
onLowAction = Maybe String
forall a. Maybe a
Nothing
  , actionThreshold :: Float
actionThreshold = Float
6
  , lowThreshold :: Float
lowThreshold = Float
10
  , highThreshold :: Float
highThreshold = Float
12
  , onlineFile :: String
onlineFile = String
"AC/online"
  , scale :: Float
scale = Float
1e6
  , onIconPattern :: Maybe IconPattern
onIconPattern = Maybe IconPattern
forall a. Maybe a
Nothing
  , offIconPattern :: Maybe IconPattern
offIconPattern = Maybe IconPattern
forall a. Maybe a
Nothing
  , idleIconPattern :: Maybe IconPattern
idleIconPattern = Maybe IconPattern
forall a. Maybe a
Nothing
  , lowString :: String
lowString = String
""
  , mediumString :: String
mediumString = String
""
  , highString :: String
highString = String
""
  , incPerc :: Bool
incPerc = Bool
False
  }

options :: [OptDescr (BattOpts -> BattOpts)]
options :: [OptDescr (BattOpts -> BattOpts)]
options =
  [ String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"O" [String
"on"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { onString :: String
onString = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"o" [String
"off"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { offString :: String
offString = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"i" [String
"idle"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { idleString :: String
idleString = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"p" [String
"positive"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { posColor :: Maybe String
posColor = String -> Maybe String
forall a. a -> Maybe a
Just String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"l" [String
"low"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { lowWColor :: Maybe String
lowWColor = String -> Maybe String
forall a. a -> Maybe a
Just String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"m" [String
"medium"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { mediumWColor :: Maybe String
mediumWColor = String -> Maybe String
forall a. a -> Maybe a
Just String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"h" [String
"high"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { highWColor :: Maybe String
highWColor = String -> Maybe String
forall a. a -> Maybe a
Just String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"L" [String
"lowt"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { lowThreshold :: Float
lowThreshold = String -> Float
forall a. Read a => String -> a
read String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"H" [String
"hight"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { highThreshold :: Float
highThreshold = String -> Float
forall a. Read a => String -> a
read String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"f" [String
"online"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { onlineFile :: String
onlineFile = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"s" [String
"scale"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o {scale :: Float
scale = String -> Float
forall a. Read a => String -> a
read String
x}) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"a" [String
"action"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { onLowAction :: Maybe String
onLowAction = String -> Maybe String
forall a. a -> Maybe a
Just String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"P" [String
"percent"] ((BattOpts -> BattOpts) -> ArgDescr (BattOpts -> BattOpts)
forall a. a -> ArgDescr a
NoArg (\BattOpts
o -> BattOpts
o {incPerc :: Bool
incPerc = Bool
True})) String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"A" [String
"action-threshold"]
               ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { actionThreshold :: Float
actionThreshold = String -> Float
forall a. Read a => String -> a
read String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"on-icon-pattern"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o ->
     BattOpts
o { onIconPattern :: Maybe IconPattern
onIconPattern = IconPattern -> Maybe IconPattern
forall a. a -> Maybe a
Just (IconPattern -> Maybe IconPattern)
-> IconPattern -> Maybe IconPattern
forall a b. (a -> b) -> a -> b
$ String -> IconPattern
parseIconPattern String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"off-icon-pattern"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o ->
     BattOpts
o { offIconPattern :: Maybe IconPattern
offIconPattern = IconPattern -> Maybe IconPattern
forall a. a -> Maybe a
Just (IconPattern -> Maybe IconPattern)
-> IconPattern -> Maybe IconPattern
forall a b. (a -> b) -> a -> b
$ String -> IconPattern
parseIconPattern String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"idle-icon-pattern"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o ->
     BattOpts
o { idleIconPattern :: Maybe IconPattern
idleIconPattern = IconPattern -> Maybe IconPattern
forall a. a -> Maybe a
Just (IconPattern -> Maybe IconPattern)
-> IconPattern -> Maybe IconPattern
forall a b. (a -> b) -> a -> b
$ String -> IconPattern
parseIconPattern String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"lows"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { lowString :: String
lowString = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"mediums"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { mediumString :: String
mediumString = String
x }) String
"") String
""
  , String
-> [String]
-> ArgDescr (BattOpts -> BattOpts)
-> String
-> OptDescr (BattOpts -> BattOpts)
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"highs"] ((String -> BattOpts -> BattOpts)
-> String -> ArgDescr (BattOpts -> BattOpts)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
x BattOpts
o -> BattOpts
o { highString :: String
highString = String
x }) String
"") String
""
  ]

data Status = Charging | Discharging | Full | Idle | Unknown deriving (ReadPrec [Status]
ReadPrec Status
Int -> ReadS Status
ReadS [Status]
(Int -> ReadS Status)
-> ReadS [Status]
-> ReadPrec Status
-> ReadPrec [Status]
-> Read Status
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Status]
$creadListPrec :: ReadPrec [Status]
readPrec :: ReadPrec Status
$creadPrec :: ReadPrec Status
readList :: ReadS [Status]
$creadList :: ReadS [Status]
readsPrec :: Int -> ReadS Status
$creadsPrec :: Int -> ReadS Status
Read, Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq)
-- Result perc watts time-seconds Status
data Result = Result Float Float Float Status | NA

sysDir :: FilePath
sysDir :: String
sysDir = String
"/sys/class/power_supply"

battConfig :: IO MConfig
battConfig :: IO MConfig
battConfig = String -> [String] -> IO MConfig
mkMConfig
       String
"Batt: <watts>, <left>% / <timeleft>" -- template
       [String
"leftbar", String
"leftvbar", String
"left", String
"acstatus", String
"timeleft", String
"watts", String
"leftipat"] -- replacements

data Files = Files
  { Files -> String
fFull :: String
  , Files -> String
fNow :: String
  , Files -> String
fVoltage :: String
  , Files -> String
fCurrent :: String
  , Files -> String
fStatus :: String
  , Files -> Bool
isCurrent :: Bool
  } | NoFiles deriving Files -> Files -> Bool
(Files -> Files -> Bool) -> (Files -> Files -> Bool) -> Eq Files
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Files -> Files -> Bool
$c/= :: Files -> Files -> Bool
== :: Files -> Files -> Bool
$c== :: Files -> Files -> Bool
Eq

data Battery = Battery
  { Battery -> Float
full :: !Float
  , Battery -> Float
now :: !Float
  , Battery -> Float
power :: !Float
  , Battery -> String
status :: !String
  }

data BatteryStatus
  = BattHigh
  | BattMedium
  | BattLow

-- | Convert the current battery charge into a 'BatteryStatus'
getBattStatus
  :: Float    -- ^ Current battery charge, assumed to be in [0,1]
  -> BattOpts -- ^ Battery options, including high/low thresholds
  -> BatteryStatus
getBattStatus :: Float -> BattOpts -> BatteryStatus
getBattStatus Float
charge BattOpts
opts
  | Float
c Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= BattOpts -> Float
highThreshold BattOpts
opts = BatteryStatus
BattHigh
  | Float
c Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= BattOpts -> Float
lowThreshold  BattOpts
opts = BatteryStatus
BattMedium
  | Bool
otherwise = BatteryStatus
BattLow
 where
   c :: Float
c = Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float -> Float
forall a. Ord a => a -> a -> a
min Float
1 Float
charge

maybeAlert :: BattOpts -> Float -> IO ()
maybeAlert :: BattOpts -> Float -> IO ()
maybeAlert BattOpts
opts Float
left =
  case BattOpts -> Maybe String
onLowAction BattOpts
opts of
    Maybe String
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    Just String
x -> Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
left Bool -> Bool -> Bool
|| BattOpts -> Float
actionThreshold BattOpts
opts Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
left)
                (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ExitCode -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ExitCode -> IO ()) -> IO ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ExitCode
system String
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 p = fromIntegral lf / 100
      w = fromIntegral rt
      t = fromIntegral tm * 60
      ac = acline == 1
      -- battery full when rate is 0 and on ac.
      sts = if (w == 0 && ac) then Full else (battStatusFbsd $ fromIntegral st)
  unless ac (maybeAlert opts p)
  return (Result p w t sts)

#else
-- | query linux battery
safeFileExist :: String -> String -> IO Bool
safeFileExist :: String -> String -> IO Bool
safeFileExist String
d String
f = (SomeException -> IO Bool) -> IO Bool -> IO Bool
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle SomeException -> IO Bool
noErrors (IO Bool -> IO Bool) -> IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
fileExist (String
d String -> String -> String
</> String
f)
  where noErrors :: SomeException -> IO Bool
noErrors = IO Bool -> SomeException -> IO Bool
forall a b. a -> b -> a
const (Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) :: SomeException -> IO Bool

batteryFiles :: String -> IO Files
batteryFiles :: String -> IO Files
batteryFiles String
bat =
  do Bool
is_charge <- String -> IO Bool
exists String
"charge_now"
     Bool
is_energy <- if Bool
is_charge then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False else String -> IO Bool
exists String
"energy_now"
     Bool
is_power <- String -> IO Bool
exists String
"power_now"
     Bool
plain <- String -> IO Bool
exists (if Bool
is_charge then String
"charge_full" else String
"energy_full")
     let cf :: String
cf = if Bool
is_power then String
"power_now" else String
"current_now"
         sf :: String
sf = if Bool
plain then String
"" else String
"_design"
     Files -> IO Files
forall (m :: * -> *) a. Monad m => a -> m a
return (Files -> IO Files) -> Files -> IO Files
forall a b. (a -> b) -> a -> b
$ case (Bool
is_charge, Bool
is_energy) of
       (Bool
True, Bool
_) -> String -> String -> String -> Bool -> Files
files String
"charge" String
cf String
sf Bool
is_power
       (Bool
_, Bool
True) -> String -> String -> String -> Bool -> Files
files String
"energy" String
cf String
sf Bool
is_power
       (Bool, Bool)
_ -> Files
NoFiles
  where prefix :: String
prefix = String
sysDir String -> String -> String
</> String
bat
        exists :: String -> IO Bool
exists = String -> String -> IO Bool
safeFileExist String
prefix
        files :: String -> String -> String -> Bool -> Files
files String
ch String
cf String
sf Bool
ip = Files :: String -> String -> String -> String -> String -> Bool -> Files
Files { fFull :: String
fFull = String
prefix String -> String -> String
</> String
ch String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_full" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
sf
                                  , fNow :: String
fNow = String
prefix String -> String -> String
</> String
ch String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_now"
                                  , fCurrent :: String
fCurrent = String
prefix String -> String -> String
</> String
cf
                                  , fVoltage :: String
fVoltage = String
prefix String -> String -> String
</> String
"voltage_now"
                                  , fStatus :: String
fStatus = String
prefix String -> String -> String
</> String
"status"
                                  , isCurrent :: Bool
isCurrent = Bool -> Bool
not Bool
ip}

haveAc :: FilePath -> IO Bool
haveAc :: String -> IO Bool
haveAc String
f =
  (SomeException -> IO Bool) -> IO Bool -> IO Bool
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle SomeException -> IO Bool
onError (IO Bool -> IO Bool) -> IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ String -> IOMode -> (Handle -> IO Bool) -> IO Bool
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile (String
sysDir String -> String -> String
</> String
f) IOMode
ReadMode ((String -> Bool) -> IO String -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"1") (IO String -> IO Bool)
-> (Handle -> IO String) -> Handle -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO String
hGetLine)
  where onError :: SomeException -> IO Bool
onError = IO Bool -> SomeException -> IO Bool
forall a b. a -> b -> a
const (Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) :: SomeException -> IO Bool

readBattery :: Float -> Files -> IO Battery
readBattery :: Float -> Files -> IO Battery
readBattery Float
_ Files
NoFiles = Battery -> IO Battery
forall (m :: * -> *) a. Monad m => a -> m a
return (Battery -> IO Battery) -> Battery -> IO Battery
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float -> String -> Battery
Battery Float
0 Float
0 Float
0 String
"Unknown"
readBattery Float
sc Files
files =
    do Float
a <- String -> IO Float
grab (String -> IO Float) -> String -> IO Float
forall a b. (a -> b) -> a -> b
$ Files -> String
fFull Files
files
       Float
b <- String -> IO Float
grab (String -> IO Float) -> String -> IO Float
forall a b. (a -> b) -> a -> b
$ Files -> String
fNow Files
files
       Float
d <- String -> IO Float
grab (String -> IO Float) -> String -> IO Float
forall a b. (a -> b) -> a -> b
$ Files -> String
fCurrent Files
files
       String
s <- String -> IO String
grabs (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ Files -> String
fStatus Files
files
       let sc' :: Float
sc' = if Files -> Bool
isCurrent Files
files then Float
sc Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
10 else Float
sc
           a' :: Float
a' = Float -> Float -> Float
forall a. Ord a => a -> a -> a
max Float
a Float
b -- sometimes the reported max charge is lower than
       Battery -> IO Battery
forall (m :: * -> *) a. Monad m => a -> m a
return (Battery -> IO Battery) -> Battery -> IO Battery
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float -> String -> Battery
Battery (Float
3600 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
a' Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
sc') -- wattseconds
                        (Float
3600 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
b Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
sc') -- wattseconds
                        (Float -> Float
forall a. Num a => a -> a
abs Float
d Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
sc') -- watts
                        String
s -- string: Discharging/Charging/Full
    where grab :: String -> IO Float
grab String
f = (SomeException -> IO Float) -> IO Float -> IO Float
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle SomeException -> IO Float
onError (IO Float -> IO Float) -> IO Float -> IO Float
forall a b. (a -> b) -> a -> b
$ String -> IOMode -> (Handle -> IO Float) -> IO Float
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
f IOMode
ReadMode ((String -> Float) -> IO String -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Float
forall a. Read a => String -> a
read (IO String -> IO Float)
-> (Handle -> IO String) -> Handle -> IO Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO String
hGetLine)
          onError :: SomeException -> IO Float
onError = IO Float -> SomeException -> IO Float
forall a b. a -> b -> a
const (Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return (-Float
1)) :: SomeException -> IO Float
          grabs :: String -> IO String
grabs String
f = (SomeException -> IO String) -> IO String -> IO String
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle SomeException -> IO String
onError' (IO String -> IO String) -> IO String -> IO String
forall a b. (a -> b) -> a -> b
$ String -> IOMode -> (Handle -> IO String) -> IO String
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
f IOMode
ReadMode Handle -> IO String
hGetLine
          onError' :: SomeException -> IO String
onError' = IO String -> SomeException -> IO String
forall a b. a -> b -> a
const (String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Unknown") :: SomeException -> IO String

-- sortOn is only available starting at ghc 7.10
sortOn :: Ord b => (a -> b) -> [a] -> [a]
sortOn :: (a -> b) -> [a] -> [a]
sortOn a -> b
f =
  ((b, a) -> a) -> [(b, a)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (b, a) -> a
forall a b. (a, b) -> b
snd ([(b, a)] -> [a]) -> ([a] -> [(b, a)]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((b, a) -> (b, a) -> Ordering) -> [(b, a)] -> [(b, a)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((b, a) -> b) -> (b, a) -> (b, a) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (b, a) -> b
forall a b. (a, b) -> a
fst) ([(b, a)] -> [(b, a)]) -> ([a] -> [(b, a)]) -> [a] -> [(b, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (b, a)) -> [a] -> [(b, a)]
forall a b. (a -> b) -> [a] -> [b]
map (\a
x -> let y :: b
y = a -> b
f a
x in b
y b -> (b, a) -> (b, a)
`seq` (b
y, a
x))

mostCommonDef :: Eq a => a -> [a] -> a
mostCommonDef :: a -> [a] -> a
mostCommonDef a
x [a]
xs = [a] -> a
forall a. [a] -> a
head ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ [[a]] -> [a]
forall a. [a] -> a
last ([[a]] -> [a]) -> [[a]] -> [a]
forall a b. (a -> b) -> a -> b
$ [a
x] [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: ([a] -> Int) -> [[a]] -> [[a]]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
group [a]
xs)

readBatteriesLinux :: BattOpts -> [Files] -> IO Result
readBatteriesLinux :: BattOpts -> [Files] -> IO Result
readBatteriesLinux BattOpts
opts [Files]
bfs =
    do let bfs' :: [Files]
bfs' = (Files -> Bool) -> [Files] -> [Files]
forall a. (a -> Bool) -> [a] -> [a]
filter (Files -> Files -> Bool
forall a. Eq a => a -> a -> Bool
/= Files
NoFiles) [Files]
bfs
       [Battery]
bats <- (Files -> IO Battery) -> [Files] -> IO [Battery]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Float -> Files -> IO Battery
readBattery (BattOpts -> Float
scale BattOpts
opts)) (Int -> [Files] -> [Files]
forall a. Int -> [a] -> [a]
take Int
3 [Files]
bfs')
       Bool
ac <- String -> IO Bool
haveAc (BattOpts -> String
onlineFile BattOpts
opts)
       let sign :: Float
sign = if Bool
ac then Float
1 else -Float
1
           ft :: Float
ft = [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Battery -> Float) -> [Battery] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Battery -> Float
full [Battery]
bats)
           left :: Float
left = if Float
ft Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0 then [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Battery -> Float) -> [Battery] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Battery -> Float
now [Battery]
bats) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
ft else Float
0
           watts :: Float
watts = Float
sign Float -> Float -> Float
forall a. Num a => a -> a -> a
* [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Battery -> Float) -> [Battery] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Battery -> Float
power [Battery]
bats)
           time :: Float
time = if Float
watts Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0 then Float
0 else Float -> Float -> Float
forall a. Ord a => a -> a -> a
max Float
0 ([Float] -> Float
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Float] -> Float) -> [Float] -> Float
forall a b. (a -> b) -> a -> b
$ (Battery -> Float) -> [Battery] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Battery -> Float
time' [Battery]
bats)
           mwatts :: Float
mwatts = if Float
watts Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0 then Float
1 else Float
sign Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
watts
           time' :: Battery -> Float
time' Battery
b = (if Bool
ac then Battery -> Float
full Battery
b Float -> Float -> Float
forall a. Num a => a -> a -> a
- Battery -> Float
now Battery
b else Battery -> Float
now Battery
b) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
mwatts
           statuses :: [Status]
           statuses :: [Status]
statuses = (String -> Status) -> [String] -> [Status]
forall a b. (a -> b) -> [a] -> [b]
map (Status -> Maybe Status -> Status
forall a. a -> Maybe a -> a
fromMaybe Status
Unknown (Maybe Status -> Status)
-> (String -> Maybe Status) -> String -> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Status
forall a. Read a => String -> Maybe a
readMaybe)
                          ([String] -> [String]
forall a. Ord a => [a] -> [a]
sort ((Battery -> String) -> [Battery] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Battery -> String
status [Battery]
bats))
           acst :: Status
acst = Status -> [Status] -> Status
forall a. Eq a => a -> [a] -> a
mostCommonDef Status
Unknown ([Status] -> Status) -> [Status] -> Status
forall a b. (a -> b) -> a -> b
$ (Status -> Bool) -> [Status] -> [Status]
forall a. (a -> Bool) -> [a] -> [a]
filter (Status
UnknownStatus -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/=) [Status]
statuses
           racst :: Status
racst | Status
acst Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/= Status
Unknown = Status
acst
                 | Float
time Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0 = Status
Idle
                 | Bool
ac = Status
Charging
                 | Bool
otherwise = Status
Discharging
       Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
ac (BattOpts -> Float -> IO ()
maybeAlert BattOpts
opts Float
left)
       Result -> IO Result
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ if Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
left then Result
NA else Float -> Float -> Float -> Status -> Result
Result Float
left Float
watts Float
time Status
racst
#endif

runBatt :: [String] -> Monitor String
runBatt :: [String] -> Monitor String
runBatt = [String] -> [String] -> Monitor String
runBatt' [String
"BAT", String
"BAT0", String
"BAT1", String
"BAT2"]

runBatt' :: [String] -> [String] -> Monitor String
runBatt' :: [String] -> [String] -> Monitor String
runBatt' [String]
bfs [String]
args = do
  BattOpts
opts <- IO BattOpts -> Monitor BattOpts
forall a. IO a -> Monitor a
io (IO BattOpts -> Monitor BattOpts)
-> IO BattOpts -> Monitor BattOpts
forall a b. (a -> b) -> a -> b
$ [OptDescr (BattOpts -> BattOpts)]
-> BattOpts -> [String] -> IO BattOpts
forall opts.
[OptDescr (opts -> opts)] -> opts -> [String] -> IO opts
parseOptsWith [OptDescr (BattOpts -> BattOpts)]
options BattOpts
defaultOpts [String]
args
#ifdef FREEBSD
  c <- io $ readBatteriesFbsd opts
#else
  Result
c <- IO Result -> Monitor Result
forall a. IO a -> Monitor a
io (IO Result -> Monitor Result) -> IO Result -> Monitor Result
forall a b. (a -> b) -> a -> b
$ BattOpts -> [Files] -> IO Result
readBatteriesLinux BattOpts
opts ([Files] -> IO Result) -> IO [Files] -> IO Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> IO Files) -> [String] -> IO [Files]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO Files
batteryFiles [String]
bfs
#endif
  Result -> BattOpts -> Monitor String
formatResult Result
c BattOpts
opts

formatResult :: Result -> BattOpts -> Monitor String
formatResult :: Result -> BattOpts -> Monitor String
formatResult Result
res BattOpts
bopt = do
  let sp :: Bool
sp = BattOpts -> Bool
incPerc BattOpts
bopt
  Bool
suffix <- Selector Bool -> Monitor Bool
forall a. Selector a -> Monitor a
getConfigValue Selector Bool
useSuffix
  Int
d <- Selector Int -> Monitor Int
forall a. Selector a -> Monitor a
getConfigValue Selector Int
decDigits
  String
nas <- Selector String -> Monitor String
forall a. Selector a -> Monitor a
getConfigValue Selector String
naString
  case Result
res of
    Result Float
x Float
w Float
t Status
s ->
      do [String]
l <- Float -> Bool -> Monitor [String]
fmtPercent Float
x Bool
sp
         String
ws <- Float -> BattOpts -> Bool -> Int -> Monitor String
fmtWatts Float
w BattOpts
bopt Bool
suffix Int
d
         String
si <- BattOpts -> Status -> Float -> Monitor String
getIconPattern BattOpts
bopt Status
s Float
x
         String
st <- String -> Float -> Monitor String
forall a. (Num a, Ord a) => String -> a -> Monitor String
showWithColors'
                 (BattOpts -> Status -> String -> BatteryStatus -> String
fmtStatus BattOpts
bopt Status
s String
nas (Float -> BattOpts -> BatteryStatus
getBattStatus Float
x BattOpts
bopt))
                 (Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
x)
         [String] -> Monitor String
parseTemplate ([String]
l [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
st, Integer -> String
fmtTime (Integer -> String) -> Integer -> String
forall a b. (a -> b) -> a -> b
$ Float -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor Float
t, String
ws, String
si])
    Result
NA -> Selector String -> Monitor String
forall a. Selector a -> Monitor a
getConfigValue Selector String
naString
  where fmtPercent :: Float -> Bool -> Monitor [String]
        fmtPercent :: Float -> Bool -> Monitor [String]
fmtPercent Float
x Bool
sp = do
          let x' :: Float
x' = [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Float
1, Float
x]
          String
pc <- if Bool
sp then Float -> String -> Monitor String
forall a. (Num a, Ord a) => a -> String -> Monitor String
colorizeString (Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
x') String
"%" else String -> Monitor String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
          String
p <- Float -> Monitor String
showPercentWithColors Float
x'
          String
b <- Float -> Float -> Monitor String
showPercentBar (Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
x') Float
x'
          String
vb <- Float -> Float -> Monitor String
showVerticalBar (Float
100 Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
x') Float
x'
          [String] -> Monitor [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String
b, String
vb, String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
pc]
        fmtWatts :: Float -> BattOpts -> Bool -> Int -> Monitor String
fmtWatts Float
x BattOpts
o Bool
s Int
d = do
          String
ws <- String -> Monitor String
showWithPadding (String -> Monitor String) -> String -> Monitor String
forall a b. (a -> b) -> a -> b
$ Int -> Float -> String
forall a. RealFloat a => Int -> a -> String
showDigits Int
d Float
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ (if Bool
s then String
"W" else String
"")
          String -> Monitor String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Monitor String) -> String -> Monitor String
forall a b. (a -> b) -> a -> b
$ Float -> BattOpts -> String -> String
color Float
x BattOpts
o String
ws
        fmtTime :: Integer -> String
        fmtTime :: Integer -> String
fmtTime Integer
x = String
hours String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ if String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
minutes Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2
                                    then String
minutes else Char
'0' Char -> String -> String
forall a. a -> [a] -> [a]
: String
minutes
          where hours :: String
hours = Integer -> String
forall a. Show a => a -> String
show (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
3600)
                minutes :: String
minutes = Integer -> String
forall a. Show a => a -> String
show ((Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
3600) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
60)
        fmtStatus
          :: BattOpts
          -> Status
          -> String -- ^ What to in case battery status is unknown
          -> BatteryStatus
          -> String
        fmtStatus :: BattOpts -> Status -> String -> BatteryStatus -> String
fmtStatus BattOpts
opts Status
Idle String
_ BatteryStatus
_ = BattOpts -> String
idleString BattOpts
opts
        fmtStatus BattOpts
_ Status
Unknown String
na BatteryStatus
_ = String
na
        fmtStatus BattOpts
opts Status
Full String
_ BatteryStatus
_ = BattOpts -> String
idleString BattOpts
opts
        fmtStatus BattOpts
opts Status
Charging String
_ BatteryStatus
_ = BattOpts -> String
onString BattOpts
opts
        fmtStatus BattOpts
opts Status
Discharging String
_ BatteryStatus
battStatus =
          (case BatteryStatus
battStatus of
            BatteryStatus
BattHigh -> BattOpts -> String
highString
            BatteryStatus
BattMedium -> BattOpts -> String
mediumString
            BatteryStatus
BattLow -> BattOpts -> String
lowString) BattOpts
opts String -> String -> String
forall a. [a] -> [a] -> [a]
++ BattOpts -> String
offString BattOpts
opts
        maybeColor :: Maybe String -> String -> String
maybeColor Maybe String
Nothing String
str = String
str
        maybeColor (Just String
c) String
str = String
"<fc=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
str String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"</fc>"
        color :: Float -> BattOpts -> String -> String
color Float
x BattOpts
o | Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0 = Maybe String -> String -> String
maybeColor (BattOpts -> Maybe String
posColor BattOpts
o)
                  | -Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= BattOpts -> Float
highThreshold BattOpts
o = Maybe String -> String -> String
maybeColor (BattOpts -> Maybe String
highWColor BattOpts
o)
                  | -Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= BattOpts -> Float
lowThreshold BattOpts
o = Maybe String -> String -> String
maybeColor (BattOpts -> Maybe String
mediumWColor BattOpts
o)
                  | Bool
otherwise = Maybe String -> String -> String
maybeColor (BattOpts -> Maybe String
lowWColor BattOpts
o)
        getIconPattern :: BattOpts -> Status -> Float -> Monitor String
getIconPattern BattOpts
opts Status
st Float
x = do
          let x' :: Float
x' = [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Float
1, Float
x]
          case Status
st of
               Status
Unknown -> Maybe IconPattern -> Float -> Monitor String
showIconPattern (BattOpts -> Maybe IconPattern
offIconPattern BattOpts
opts) Float
x'
               Status
Idle -> Maybe IconPattern -> Float -> Monitor String
showIconPattern (BattOpts -> Maybe IconPattern
idleIconPattern BattOpts
opts) Float
x'
               Status
Full -> Maybe IconPattern -> Float -> Monitor String
showIconPattern (BattOpts -> Maybe IconPattern
idleIconPattern BattOpts
opts) Float
x'
               Status
Charging -> Maybe IconPattern -> Float -> Monitor String
showIconPattern (BattOpts -> Maybe IconPattern
onIconPattern BattOpts
opts) Float
x'
               Status
Discharging -> Maybe IconPattern -> Float -> Monitor String
showIconPattern (BattOpts -> Maybe IconPattern
offIconPattern BattOpts
opts) Float
x'