module Xmobar.Plugins.Monitors.Uptime (uptimeConfig, runUptime) where
import Xmobar.Plugins.Monitors.Common
import qualified Data.ByteString.Lazy.Char8 as B
uptimeConfig :: IO MConfig
uptimeConfig :: IO MConfig
uptimeConfig = String -> [String] -> IO MConfig
mkMConfig String
"Up <days>d <hours>h <minutes>m"
[String
"days", String
"hours", String
"minutes", String
"seconds"]
readUptime :: IO Float
readUptime :: IO Float
readUptime =
(ByteString -> Float) -> IO ByteString -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> Float
forall a. Read a => String -> a
read (String -> Float) -> (ByteString -> String) -> ByteString -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
B.unpack (ByteString -> String)
-> (ByteString -> ByteString) -> ByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. [a] -> a
head ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
B.words) (String -> IO ByteString
B.readFile String
"/proc/uptime")
secsPerDay :: Integer
secsPerDay :: Integer
secsPerDay = Integer
24 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
3600
uptime :: Monitor [String]
uptime :: Monitor [String]
uptime = do
Float
t <- IO Float -> Monitor Float
forall a. IO a -> Monitor a
io IO Float
readUptime
Bool
u <- Selector Bool -> Monitor Bool
forall a. Selector a -> Monitor a
getConfigValue Selector Bool
useSuffix
let tsecs :: Integer
tsecs = Float -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor Float
t
secs :: Integer
secs = Integer
tsecs Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
secsPerDay
days :: Integer
days = Integer
tsecs Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
secsPerDay
hours :: Integer
hours = Integer
secs Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
3600
mins :: Integer
mins = (Integer
secs 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
ss :: Integer
ss = Integer
secs Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
60
str :: a -> String -> String
str a
x String
s = if Bool
u then a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s else a -> String
forall a. Show a => a -> String
show a
x
(String -> ReaderT MConfig IO String)
-> [String] -> Monitor [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (String -> Integer -> ReaderT MConfig IO String
forall a.
(Num a, Ord a) =>
String -> a -> ReaderT MConfig IO String
`showWithColors'` Integer
days)
[Integer -> String -> String
forall a. Show a => a -> String -> String
str Integer
days String
"d", Integer -> String -> String
forall a. Show a => a -> String -> String
str Integer
hours String
"h", Integer -> String -> String
forall a. Show a => a -> String -> String
str Integer
mins String
"m", Integer -> String -> String
forall a. Show a => a -> String -> String
str Integer
ss String
"s"]
runUptime :: [String] -> Monitor String
runUptime :: [String] -> ReaderT MConfig IO String
runUptime [String]
_ = Monitor [String]
uptime Monitor [String]
-> ([String] -> ReaderT MConfig IO String)
-> ReaderT MConfig IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> ReaderT MConfig IO String
parseTemplate