Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / CPUload.hs @ 798582cf

History | View | Annotate | Download (5.8 kB)

1
{-| @/proc/stat@ data collector.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2013 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.DataCollectors.CPUload
27
  ( dcName
28
  , dcVersion
29
  , dcFormatVersion
30
  , dcCategory
31
  , dcKind
32
  , dcReport
33
  , dcUpdate
34
  ) where
35

    
36
import qualified Control.Exception as E
37
import Data.Attoparsec.Text.Lazy as A
38
import Data.Text.Lazy (pack, unpack)
39
import qualified Text.JSON as J
40
import qualified Data.Sequence as Seq
41
import System.Posix.Unistd (getSysVar, SysVar(ClockTick))
42

    
43
import qualified Ganeti.BasicTypes as BT
44
import qualified Ganeti.Constants as C
45
import Ganeti.Cpu.LoadParser(cpustatParser)
46
import Ganeti.DataCollectors.Types
47
import Ganeti.Utils
48
import Ganeti.Cpu.Types
49

    
50
-- | The default path of the CPU status file.
51
-- It is hardcoded because it is not likely to change.
52
defaultFile :: FilePath
53
defaultFile = C.statFile
54

    
55
-- | The buffer size of the values kept in the map.
56
bufferSize :: Int
57
bufferSize = C.cpuavgloadBufferSize
58

    
59
-- | The window size of the values that will export the average load.
60
windowSize :: Integer
61
windowSize = toInteger C.cpuavgloadWindowSize
62

    
63
-- | The default setting for the maximum amount of not parsed character to
64
-- print in case of error.
65
-- It is set to use most of the screen estate on a standard 80x25 terminal.
66
-- TODO: add the possibility to set this with a command line parameter.
67
defaultCharNum :: Int
68
defaultCharNum = 80*20
69

    
70
-- | The name of this data collector.
71
dcName :: String
72
dcName = "cpu-avg-load"
73

    
74
-- | The version of this data collector.
75
dcVersion :: DCVersion
76
dcVersion = DCVerBuiltin
77

    
78
-- | The version number for the data format of this data collector.
79
dcFormatVersion :: Int
80
dcFormatVersion = 1
81

    
82
-- | The category of this data collector.
83
dcCategory :: Maybe DCCategory
84
dcCategory = Nothing
85

    
86
-- | The kind of this data collector.
87
dcKind :: DCKind
88
dcKind = DCKPerf
89

    
90
-- | The data exported by the data collector, taken from the default location.
91
dcReport :: Maybe CollectorData -> IO DCReport
92
dcReport colData =
93
  let cpuLoadData =
94
        case colData of
95
          Nothing -> Seq.empty
96
          Just colData' ->
97
            case colData' of
98
              CPULoadData v -> v
99
  in buildDCReport cpuLoadData
100
-- | Data stored by the collector in mond's memory.
101
type Buffer = Seq.Seq (Integer, [Int])
102

    
103
-- | Compute the load from a CPU.
104
computeLoad :: CPUstat -> Int
105
computeLoad cpuData =
106
  csUser cpuData + csNice cpuData + csSystem cpuData
107
  + csIowait cpuData + csIrq cpuData + csSoftirq cpuData
108
  + csSteal cpuData + csGuest cpuData + csGuestNice cpuData
109

    
110
-- | Reads and Computes the load for each CPU.
111
dcCollectFromFile :: FilePath -> IO (Integer, [Int])
112
dcCollectFromFile inputFile = do
113
  contents <-
114
    ((E.try $ readFile inputFile) :: IO (Either IOError String)) >>=
115
      exitIfBad "reading from file" . either (BT.Bad . show) BT.Ok
116
  cpustatData <-
117
    case A.parse cpustatParser $ pack contents of
118
      A.Fail unparsedText contexts errorMessage -> exitErr $
119
        show (Prelude.take defaultCharNum $ unpack unparsedText) ++ "\n"
120
          ++ show contexts ++ "\n" ++ errorMessage
121
      A.Done _ cpustatD -> return cpustatD
122
  now <- getCurrentTime
123
  let timestamp = now :: Integer
124
  return (timestamp, map computeLoad cpustatData)
125

    
126
-- | Returns the collected data in the appropriate type.
127
dcCollect :: IO Buffer
128
dcCollect  = do
129
  l <- dcCollectFromFile defaultFile
130
  return (Seq.singleton l)
131

    
132
-- | Formats data for JSON transformation.
133
formatData :: [Double] -> CPUavgload
134
formatData [] = CPUavgload (0 :: Int) [] (0 :: Double)
135
formatData l@(x:xs) = CPUavgload (length l - 1) xs x
136

    
137
-- | Update a Map Entry.
138
updateEntry :: Buffer -> Buffer -> Buffer
139
updateEntry newBuffer mapEntry =
140
  (Seq.><) newBuffer
141
  (if Seq.length mapEntry < bufferSize
142
    then mapEntry
143
    else Seq.drop 1 mapEntry)
144

    
145
-- | Updates the given Collector data.
146
dcUpdate :: Maybe CollectorData -> IO CollectorData
147
dcUpdate mcd = do
148
  v <- dcCollect
149
  let new_v =
150
        case mcd of
151
          Nothing -> v
152
          Just cd ->
153
            case cd of
154
              CPULoadData old_v -> updateEntry v old_v
155
  new_v `seq` return $ CPULoadData new_v
156

    
157
-- | Computes the average load for every CPU and the overall from data read
158
-- from the map.
159
computeAverage :: Buffer -> Integer -> Integer -> [Double]
160
computeAverage s w ticks =
161
  let window = Seq.takeWhileL ((> w) . fst) s
162
      go Seq.EmptyL          _                    = []
163
      go _                   Seq.EmptyR           = []
164
      go (leftmost Seq.:< _) (_ Seq.:> rightmost) = do
165
        let (timestampL, listL) = leftmost
166
            (timestampR, listR) = rightmost
167
            work = zipWith (-) listL listR
168
            overall = (timestampL - timestampR) * ticks
169
        map (\x -> fromIntegral x / fromIntegral overall) work
170
  in go (Seq.viewl window) (Seq.viewr window)
171

    
172
-- | This function computes the JSON representation of the CPU load.
173
buildJsonReport :: Buffer -> IO J.JSValue
174
buildJsonReport v = do
175
  ticks <- getSysVar ClockTick
176
  let res = computeAverage v windowSize ticks
177
  return . J.showJSON $ formatData res
178

    
179
-- | This function computes the DCReport for the CPU load.
180
buildDCReport :: Buffer -> IO DCReport
181
buildDCReport v  =
182
  buildJsonReport v >>=
183
    buildReport dcName dcVersion dcFormatVersion dcCategory dcKind