{-# LANGUAGE DataKinds #-} module Main (main) where import qualified Prelude import Control.Applicative import Data.Maybe import Data.Map (Map); import qualified Data.Map as Map import Numeric.Units.Dimensional.Prelude hiding (lookup,showIn) import Numeric.Units.Dimensional.UnitNames (atom) import Parser import System.Environment import Text.Megaparsec import Text.Printf main :: IO () main = do [p] <- getArgs parse ueventFile p <$> readFile p >>= either printError printPowerSupply printError :: ParseError (Token String) Dec -> IO () printError = print . show printPowerSupply :: Map String String -> IO () printPowerSupply x = do putStrLn $ "capacity: " ++ showIn percent capacity putStrLn $ "chargeFull: " ++ showIn (milli ampere * hour) chargeFull putStrLn $ "chargeNow: " ++ showIn (milli ampere * hour) chargeNow putStrLn $ "currentNow: " ++ showIn (milli ampere) currentNow putStrLn $ "energyFull: " ++ showIn (watt * hour) energyFull putStrLn $ "energyNow: " ++ showIn (watt * hour) energyNow putStrLn $ "powerNow: " ++ showIn watt powerNow putStrLn $ "timeRemain: " ++ showHourMinute timeRemain putStrLn $ "voltageNow: " ++ showIn volt voltageNow putStrLn $ "voltageMin: " ++ showIn volt voltageMin where chargeFull = fromMaybe (energyFull / voltageMin) (getQty (micro ampere * hour) "POWER_SUPPLY_CHARGE_FULL" x) chargeNow = fromMaybe (energyNow / voltageMin) (getQty (micro ampere * hour) "POWER_SUPPLY_CHARGE_NOW" x) currentNow = fromMaybe (powerNow / voltageNow) (getQty (micro ampere) "POWER_SUPPLY_CURRENT_NOW" x) energyFull = fromMaybe (chargeFull * voltageMin) (getQty (micro watt * hour) "POWER_SUPPLY_ENERGY_FULL" x) energyNow = fromMaybe (chargeNow * voltageMin) (getQty (micro watt * hour) "POWER_SUPPLY_ENERGY_NOW" x) powerNow = fromMaybe (currentNow * voltageNow) (getQty (micro watt) "POWER_SUPPLY_POWER_NOW" x) voltageNow = fromMaybe (error "no voltageNow") (getQty (micro volt) "POWER_SUPPLY_VOLTAGE_NOW" x) voltageMin = fromMaybe (error "no voltageMin") (getQty (micro volt) "POWER_SUPPLY_VOLTAGE_MIN_DESIGN" x) capacity = chargeNow / chargeFull timeRemain = chargeNow / currentNow getQty :: (Ord k, Num a) => Unit m d a -> k -> Map k String -> Maybe (Quantity d a) getQty u k x = (*~ u) . fromIntegral <$> (parseMaybe decimal =<< Map.lookup k x) percent :: Unit 'NonMetric DOne Double percent = mkUnitQ (atom "%" "%" "percent") (1 Prelude./ 100) one scale :: Double -> Int scale v | v == 0 || v >= 100 = 0 | v >= 10 = 1 | v >= 1 = 2 | otherwise = 3 showIn :: Unit m d Double -> Quantity d Double -> String showIn u q | isInfinite v = "inf" | otherwise = printf "%.*f%s" (scale v) v (showUnit u) where v = q /~ u :: Double showHourMinute :: Quantity DTime Double -> String showHourMinute q | isInfinite v = "inf" | otherwise = printf "%dh%dm" h m where (h,hfrac) = properFraction v :: (Integer,Double) m = round $ 60 Prelude.* hfrac :: Integer v = q /~ hour :: Double showUnit :: Unit m d a -> String showUnit = filter (/=' ') . show . name --showBar :: Int -> Double -> String --showBar n r = -- pp (SGR color (Plain (take t1 (repeat '■'))) <> -- SGR [30] (Plain (take t2 (repeat '■')))) -- where -- color -- | r >= 0.42 = [1,32] -- | r >= 0.23 = [1,33] -- | r >= 0.11 = [1,31] -- | otherwise = [5,1,31] -- t1 = truncate (r * fromIntegral n) -- t2 = n - t1