--------------------------------------------------------------------------------
-- |
-- Module      : System.Taffybar.Information.StreamInfo
-- Copyright   : (c) José A. Romero L.
-- License     : BSD3-style (see LICENSE)
--
-- Maintainer  : José A. Romero L. <escherdragon@gmail.com>
-- Stability   : unstable
-- Portability : unportable
--
-- Generic code to poll any of the many data files maintained by the kernel in
-- POSIX systems. Provides methods for applying a custom parsing function to the
-- contents of the file and to calculate differentials across one or more values
-- provided via the file.
--
--------------------------------------------------------------------------------

module System.Taffybar.Information.StreamInfo
    ( getParsedInfo
    , getLoad
    , getAccLoad
    , getTransfer
    ) where

import Control.Concurrent ( threadDelay )
import Data.IORef
import Data.Maybe ( fromMaybe )

-- | Apply the given parser function to the file under the given path to produce
-- a lookup map, then use the given selector as key to extract from it the
-- desired value.
getParsedInfo :: FilePath -> (String -> [(String, [a])]) -> String -> IO [a]
getParsedInfo :: forall a.
FilePath -> (FilePath -> [(FilePath, [a])]) -> FilePath -> IO [a]
getParsedInfo FilePath
path FilePath -> [(FilePath, [a])]
parser FilePath
selector = do
    FilePath
file <- FilePath -> IO FilePath
readFile FilePath
path
    FilePath -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
file Int -> IO () -> IO ()
`seq` () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    [a] -> IO [a]
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> Maybe [a] -> [a]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [a] -> [a]) -> Maybe [a] -> [a]
forall a b. (a -> b) -> a -> b
$ FilePath -> [(FilePath, [a])] -> Maybe [a]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FilePath
selector ([(FilePath, [a])] -> Maybe [a]) -> [(FilePath, [a])] -> Maybe [a]
forall a b. (a -> b) -> a -> b
$ FilePath -> [(FilePath, [a])]
parser FilePath
file)

truncVal :: (RealFloat a) => a -> a
truncVal :: forall a. RealFloat a => a -> a
truncVal a
v
  | a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
v Bool -> Bool -> Bool
|| a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0.0 = a
0.0
  | Bool
otherwise = a
v

-- | Convert the given list of Integer to a list of the ratios of each of its
-- elements against their sum.
toRatioList :: (Integral a, RealFloat b) => [a] -> [b]
toRatioList :: forall a b. (Integral a, RealFloat b) => [a] -> [b]
toRatioList [a]
deltas = (b -> b) -> [b] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map b -> b
forall a. RealFloat a => a -> a
truncVal [b]
ratios
    where total :: b
total = a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
$ [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [a]
deltas
          ratios :: [b]
ratios = (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map ((b -> b -> b
forall a. Fractional a => a -> a -> a
/b
total) (b -> b) -> (a -> b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral) [a]
deltas

-- | Execute the given action twice with the given delay in-between and return
-- the difference between the two samples.
probe :: (Num a, RealFrac b) => IO [a] -> b -> IO [a]
probe :: forall a b. (Num a, RealFrac b) => IO [a] -> b -> IO [a]
probe IO [a]
action b
delay = do
    [a]
a <- IO [a]
action
    Int -> IO ()
threadDelay (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ b -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (b
delay b -> b -> b
forall a. Num a => a -> a -> a
* b
1e6)
    [a]
b <- IO [a]
action
    [a] -> IO [a]
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> IO [a]) -> [a] -> IO [a]
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [a]
b [a]
a

-- | Execute the given action once and return the difference between the
-- obtained sample and the one contained in the given IORef.
accProbe :: (Num a) => IO [a] -> IORef [a] -> IO [a]
accProbe :: forall a. Num a => IO [a] -> IORef [a] -> IO [a]
accProbe IO [a]
action IORef [a]
sample = do
    [a]
a <- IORef [a] -> IO [a]
forall a. IORef a -> IO a
readIORef IORef [a]
sample
    [a]
b <- IO [a]
action
    IORef [a] -> [a] -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef [a]
sample [a]
b
    [a] -> IO [a]
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> IO [a]) -> [a] -> IO [a]
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [a]
b [a]
a

-- | Probe the given action and, interpreting the result as a variation in time,
-- return the speed of change of its values.
getTransfer :: (Integral a, RealFloat b) => b -> IO [a] -> IO [b]
getTransfer :: forall a b. (Integral a, RealFloat b) => b -> IO [a] -> IO [b]
getTransfer b
interval IO [a]
action = do
    [a]
deltas <- IO [a] -> b -> IO [a]
forall a b. (Num a, RealFrac b) => IO [a] -> b -> IO [a]
probe IO [a]
action b
interval
    [b] -> IO [b]
forall (m :: * -> *) a. Monad m => a -> m a
return ([b] -> IO [b]) -> [b] -> IO [b]
forall a b. (a -> b) -> a -> b
$ (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map (b -> b
forall a. RealFloat a => a -> a
truncVal (b -> b) -> (a -> b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> b -> b
forall a. Fractional a => a -> a -> a
/b
interval) (b -> b) -> (a -> b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral) [a]
deltas

-- | Probe the given action and return the relative variation of each of the
-- obtained values against the whole, where the whole is calculated as the sum
-- of all the values in the probe.
getLoad :: (Integral a, RealFloat b) => b -> IO [a] -> IO [b]
getLoad :: forall a b. (Integral a, RealFloat b) => b -> IO [a] -> IO [b]
getLoad b
interval IO [a]
action = [a] -> [b]
forall a b. (Integral a, RealFloat b) => [a] -> [b]
toRatioList ([a] -> [b]) -> IO [a] -> IO [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [a] -> b -> IO [a]
forall a b. (Num a, RealFrac b) => IO [a] -> b -> IO [a]
probe IO [a]
action b
interval

-- | Similar to getLoad, but execute the given action only once and use the
-- given IORef to calculate the result and to save the current value, so it
-- can be reused in the next call.
getAccLoad :: (Integral a, RealFloat b) => IORef [a] -> IO [a] -> IO [b]
getAccLoad :: forall a b.
(Integral a, RealFloat b) =>
IORef [a] -> IO [a] -> IO [b]
getAccLoad IORef [a]
sample IO [a]
action = [a] -> [b]
forall a b. (Integral a, RealFloat b) => [a] -> [b]
toRatioList ([a] -> [b]) -> IO [a] -> IO [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [a] -> IORef [a] -> IO [a]
forall a. Num a => IO [a] -> IORef [a] -> IO [a]
accProbe IO [a]
action IORef [a]
sample