module System.Taffybar.Widget.CPUMonitor where
import Control.Monad.IO.Class
import Data.IORef
import qualified GI.Gtk
import System.Taffybar.Information.CPU2 (getCPUInfo)
import System.Taffybar.Information.StreamInfo (getAccLoad)
import System.Taffybar.Widget.Generic.PollingGraph
cpuMonitorNew
:: MonadIO m
=> GraphConfig
-> Double
-> String
-> m GI.Gtk.Widget
cpuMonitorNew :: forall (m :: * -> *).
MonadIO m =>
GraphConfig -> Double -> String -> m Widget
cpuMonitorNew GraphConfig
cfg Double
interval String
cpu = IO Widget -> m Widget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
[Int]
info <- String -> IO [Int]
getCPUInfo String
cpu
IORef [Int]
sample <- [Int] -> IO (IORef [Int])
forall a. a -> IO (IORef a)
newIORef [Int]
info
GraphConfig -> Double -> IO [Double] -> IO Widget
forall (m :: * -> *).
MonadIO m =>
GraphConfig -> Double -> IO [Double] -> m Widget
pollingGraphNew GraphConfig
cfg Double
interval (IO [Double] -> IO Widget) -> IO [Double] -> IO Widget
forall a b. (a -> b) -> a -> b
$ IORef [Int] -> String -> IO [Double]
probe IORef [Int]
sample String
cpu
probe :: IORef [Int] -> String -> IO [Double]
probe :: IORef [Int] -> String -> IO [Double]
probe IORef [Int]
sample String
cpuName = do
[Double]
load <- IORef [Int] -> IO [Int] -> IO [Double]
forall a b.
(Integral a, RealFloat b) =>
IORef [a] -> IO [a] -> IO [b]
getAccLoad IORef [Int]
sample (IO [Int] -> IO [Double]) -> IO [Int] -> IO [Double]
forall a b. (a -> b) -> a -> b
$ String -> IO [Int]
getCPUInfo String
cpuName
case [Double]
load of
Double
l0:Double
l1:Double
l2:[Double]
_ -> [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ Double
l0 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
l1, Double
l2 ]
[Double]
_ -> [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []