module Monky.Examples.CPU
( getCPUHandle
, getCPUHandle'
, getNumaHandles
, getNumaHandles'
, C.ScalingType(..)
, CPUHandle
, NumaHandle
, FreqHandle
, TempHandle
, getFreqHandle
, getFreqNuma
, getTempHandle
, getTempHandle'
, getTempHandles
, getRawNumas
, getRawCPU
)
where
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Formatting
import Data.List (intercalate)
import Monky.Modules
import Monky.Examples.Images
import qualified Monky.CPU as C
#if MIN_VERSION_base(4,8,0)
#else
import Control.Applicative ((<$>))
#endif
cpuColor :: Int -> Text
cpuColor p
| p < 15 = "#00d700"
| p < 50 = "#ffff5f"
| p < 90 = "#ffd700"
| otherwise = "#ff0000"
printBar :: Int -> MonkyOut
printBar h =
MonkyColor (cpuColor h, "#262626") (MonkyBar h)
printXbm :: MonkyOut
printXbm = cpuImage
printFrequency :: Float -> MonkyOut
printFrequency = MonkyPlain . sformat (fixed 1 % "G")
printThemp :: Int -> MonkyOut
printThemp = MonkyPlain . sformat (" " % int % "°C")
getNumaNode :: C.NumaHandle -> IO [MonkyOut]
getNumaNode nh = map printBar <$> C.getNumaPercent nh
newtype RawCPU = RawCPU C.CPUHandle
newtype RawNuma = RawNuma C.NumaHandle
instance PollModule RawCPU where
getOutput (RawCPU h) =
map printBar <$> C.getCPUPercent h
instance PollModule RawNuma where
getOutput (RawNuma h) = getNumaNode h
newtype FreqHandle = FH C.FreqHandle
newtype TempHandle = TH C.TempHandle
instance PollModule FreqHandle where
getOutput (FH fh) =
return . printFrequency <$> C.getCPUMaxScalingFreq fh
instance PollModule TempHandle where
getOutput (TH th) =
return . printThemp <$> C.getCPUTemp th
data CPUHandle = CPH FreqHandle RawCPU TempHandle
data NumaHandle = NUH [(FreqHandle, RawNuma, TempHandle)]
getFreqHandle :: C.ScalingType -> IO FreqHandle
getFreqHandle = fmap FH . C.getFreqHandle
getFreqNuma :: C.ScalingType -> RawNuma -> IO FreqHandle
getFreqNuma t (RawNuma h) = FH <$> C.getFreqNuma t h
getTempHandle' :: IO TempHandle
getTempHandle' = getTempHandle . fromMaybe (error "Could not find thermal zone") =<< C.guessThermalZone
getTempHandles :: IO [TempHandle]
getTempHandles = fmap (map TH ) C.getThermalZones
getTempHandle :: String -> IO TempHandle
getTempHandle = fmap TH . C.getThermalZone
getRawCPU :: IO RawCPU
getRawCPU = RawCPU <$> C.getCPUHandle
getRawNumas :: IO [RawNuma]
getRawNumas = map RawNuma <$> C.getNumaHandles
getCPUHandle
:: C.ScalingType
-> String
-> IO CPUHandle
getCPUHandle s t = do
fh <- getFreqHandle s
raw <- getRawCPU
th <- getTempHandle t
return $ CPH fh raw th
getCPUHandle' :: C.ScalingType -> IO CPUHandle
getCPUHandle' s = do
fh <- getFreqHandle s
raw <- getRawCPU
th <- getTempHandle'
return $ CPH fh raw th
getNumaHandles
:: C.ScalingType
-> [String]
-> IO NumaHandle
getNumaHandles st zones = do
raw <- getRawNumas
th <- mapM getTempHandle zones
fh <- mapM (getFreqNuma st) raw
return . NUH $ zip3 fh raw th
getNumaHandles' :: C.ScalingType -> IO NumaHandle
getNumaHandles' st = do
raw <- getRawNumas
zones <- getTempHandles
fh <- mapM (getFreqNuma st) raw
return . NUH $ zip3 fh raw zones
formatNumaNode :: (FreqHandle, RawNuma, TempHandle) -> IO [MonkyOut]
formatNumaNode (fh, rh, th) = do
freq <- getOutput fh
raw <- getOutput rh
temp <- getOutput th
return (freq ++ raw ++ temp)
instance PollModule CPUHandle where
getOutput (CPH fh rh th) = do
cp <- getOutput rh
ct <- getOutput th
cf <- getOutput fh
return (printXbm: cf ++ cp ++ ct)
instance PollModule NumaHandle where
getOutput (NUH xs) =
(printXbm:) . intercalate [(MonkyPlain (" - "))] <$> mapM formatNumaNode xs