Revision 2da679f7

b/Makefile.am
562 562
	src/Ganeti/Curl/Multi.hs \
563 563
	src/Ganeti/Daemon.hs \
564 564
	src/Ganeti/DataCollectors/CLI.hs \
565
	src/Ganeti/DataCollectors/CPUload.hs \
565 566
	src/Ganeti/DataCollectors/Diskstats.hs \
566 567
	src/Ganeti/DataCollectors/Drbd.hs \
567 568
	src/Ganeti/DataCollectors/InstStatus.hs \
b/lib/constants.py
2542 2542

  
2543 2543
DISKSTATS_FILE = "/proc/diskstats"
2544 2544

  
2545
# CPU load collector variables
2546
STAT_FILE = "/proc/stat"
2547
CPUAVGLOAD_BUFFER_SIZE = 150
2548
CPUAVGLOAD_WINDOW_SIZE = 600
2549

  
2545 2550
# Do not re-export imported modules
2546 2551
del re, _vcsversion, _autoconf, socket, pathutils, compat
b/src/Ganeti/Cpu/Types.hs
27 27
-}
28 28
module Ganeti.Cpu.Types
29 29
  ( CPUstat(..)
30
  , CPUavgload(..)
30 31
  ) where
31 32

  
32 33
import Ganeti.THH
33 34

  
35
-- | This is the format of the report produced by the cpu load
36
-- collector.
37
$(buildObject "CPUavgload" "cav"
38
  [ simpleField "cpu_number" [t| Int |]
39
  , simpleField "cpus"       [t| [Double] |]
40
  , simpleField "cpu_total"  [t| Double |]
41
  ])
42

  
34 43
-- | This is the format of the data parsed by the input file.
35 44
$(buildObject "CPUstat" "cs"
36 45
  [ simpleField "name"       [t| String |]
b/src/Ganeti/DataCollectors/CPUload.hs
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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

  
171
-- | This function computes the JSON representation of the CPU load.
172
buildJsonReport :: Buffer -> IO J.JSValue
173
buildJsonReport v =
174
  let res = computeAverage v windowSize
175
  in return . J.showJSON $ formatData res
176

  
177
-- | This function computes the DCReport for the CPU load.
178
buildDCReport :: Buffer -> IO DCReport
179
buildDCReport v  =
180
  buildJsonReport v >>=
181
    buildReport dcName dcVersion dcFormatVersion dcCategory dcKind
b/src/Ganeti/DataCollectors/Types.hs
33 33
  , DCStatus(..)
34 34
  , DCStatusCode(..)
35 35
  , DCVersion(..)
36
  , CollectorData(..)
37
  , CollectorMap
36 38
  , buildReport
37 39
  , mergeStatuses
38 40
  ) where
39 41

  
40 42
import Data.Char
43
import qualified Data.Map as Map
44
import qualified Data.Sequence as Seq
41 45
import Text.JSON
42 46

  
43 47
import Ganeti.Constants as C
......
95 99
  showJSON (DCVersion v) = showJSON v
96 100
  readJSON = error "JSON read instance not implemented for type DCVersion"
97 101

  
102
-- | Type for the value field of the above map.
103
data CollectorData = CPULoadData (Seq.Seq (Integer, [Int]))
104

  
105
-- | Type for the map storing the data of the statefull DataCollectors.
106
type CollectorMap = Map.Map String CollectorData
107

  
98 108
-- | This is the format of the report produced by each data collector.
99 109
$(buildObject "DCReport" "dcReport"
100 110
  [ simpleField "name"           [t| String |]

Also available in: Unified diff