module Ganeti.DataCollectors.CPUload
( dcName
, dcVersion
, dcFormatVersion
, dcCategory
, dcKind
, dcReport
, dcUpdate
) where
import qualified Control.Exception as E
import Data.Attoparsec.Text.Lazy as A
import Data.Text.Lazy (pack, unpack)
import qualified Text.JSON as J
import qualified Data.Sequence as Seq
import System.Posix.Unistd (getSysVar, SysVar(ClockTick))
import qualified Ganeti.BasicTypes as BT
import qualified Ganeti.Constants as C
import Ganeti.Cpu.LoadParser(cpustatParser)
import Ganeti.DataCollectors.Types
import Ganeti.Utils
import Ganeti.Cpu.Types
defaultFile :: FilePath
defaultFile = C.statFile
bufferSize :: Int
bufferSize = C.cpuavgloadBufferSize
windowSize :: Integer
windowSize = toInteger C.cpuavgloadWindowSize
defaultCharNum :: Int
defaultCharNum = 80*20
dcName :: String
dcName = "cpu-avg-load"
dcVersion :: DCVersion
dcVersion = DCVerBuiltin
dcFormatVersion :: Int
dcFormatVersion = 1
dcCategory :: Maybe DCCategory
dcCategory = Nothing
dcKind :: DCKind
dcKind = DCKPerf
dcReport :: Maybe CollectorData -> IO DCReport
dcReport colData =
let cpuLoadData =
case colData of
Nothing -> Seq.empty
Just colData' ->
case colData' of
CPULoadData v -> v
in buildDCReport cpuLoadData
type Buffer = Seq.Seq (Integer, [Int])
computeLoad :: CPUstat -> Int
computeLoad cpuData =
csUser cpuData + csNice cpuData + csSystem cpuData
+ csIowait cpuData + csIrq cpuData + csSoftirq cpuData
+ csSteal cpuData + csGuest cpuData + csGuestNice cpuData
dcCollectFromFile :: FilePath -> IO (Integer, [Int])
dcCollectFromFile inputFile = do
contents <-
((E.try $ readFile inputFile) :: IO (Either IOError String)) >>=
exitIfBad "reading from file" . either (BT.Bad . show) BT.Ok
cpustatData <-
case A.parse cpustatParser $ pack contents of
A.Fail unparsedText contexts errorMessage -> exitErr $
show (Prelude.take defaultCharNum $ unpack unparsedText) ++ "\n"
++ show contexts ++ "\n" ++ errorMessage
A.Done _ cpustatD -> return cpustatD
now <- getCurrentTime
let timestamp = now :: Integer
return (timestamp, map computeLoad cpustatData)
dcCollect :: IO Buffer
dcCollect = do
l <- dcCollectFromFile defaultFile
return (Seq.singleton l)
formatData :: [Double] -> CPUavgload
formatData [] = CPUavgload (0 :: Int) [] (0 :: Double)
formatData l@(x:xs) = CPUavgload (length l 1) xs x
updateEntry :: Buffer -> Buffer -> Buffer
updateEntry newBuffer mapEntry =
(Seq.><) newBuffer
(if Seq.length mapEntry < bufferSize
then mapEntry
else Seq.drop 1 mapEntry)
dcUpdate :: Maybe CollectorData -> IO CollectorData
dcUpdate mcd = do
v <- dcCollect
let new_v =
case mcd of
Nothing -> v
Just cd ->
case cd of
CPULoadData old_v -> updateEntry v old_v
new_v `seq` return $ CPULoadData new_v
computeAverage :: Buffer -> Integer -> Integer -> [Double]
computeAverage s w ticks =
let window = Seq.takeWhileL ((> w) . fst) s
go Seq.EmptyL _ = []
go _ Seq.EmptyR = []
go (leftmost Seq.:< _) (_ Seq.:> rightmost) = do
let (timestampL, listL) = leftmost
(timestampR, listR) = rightmost
work = zipWith () listL listR
overall = (timestampL timestampR) * ticks
map (\x -> fromIntegral x / fromIntegral overall) work
in go (Seq.viewl window) (Seq.viewr window)
buildJsonReport :: Buffer -> IO J.JSValue
buildJsonReport v = do
ticks <- getSysVar ClockTick
let res = computeAverage v windowSize ticks
return . J.showJSON $ formatData res
buildDCReport :: Buffer -> IO DCReport
buildDCReport v =
buildJsonReport v >>=
buildReport dcName dcVersion dcFormatVersion dcCategory dcKind