Revision f6d4b52d

b/Makefile.am
68 68
	src/Ganeti \
69 69
	src/Ganeti/Confd \
70 70
	src/Ganeti/Curl \
71
	src/Ganeti/Cpu \
71 72
	src/Ganeti/DataCollectors \
72 73
	src/Ganeti/HTools \
73 74
	src/Ganeti/HTools/Backend \
......
556 557
	src/Ganeti/Confd/Utils.hs \
557 558
	src/Ganeti/Config.hs \
558 559
	src/Ganeti/ConfigReader.hs \
560
	src/Ganeti/Cpu/LoadParser.hs \
561
	src/Ganeti/Cpu/Types.hs \
559 562
	src/Ganeti/Curl/Multi.hs \
560 563
	src/Ganeti/Daemon.hs \
561 564
	src/Ganeti/DataCollectors/CLI.hs \
b/src/Ganeti/Cpu/LoadParser.hs
1
{-# LANGUAGE OverloadedStrings #-}
2
{-| /proc/stat file parser
3

  
4
This module holds the definition of the parser that extracts information
5
about the CPU load of the system from the @/proc/stat@ file.
6

  
7
-}
8
{-
9

  
10
Copyright (C) 2013 Google Inc.
11

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

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

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

  
27
-}
28
module Ganeti.Cpu.LoadParser (cpustatParser) where
29

  
30
import Control.Applicative ((<*>), (<*), (*>), (<$>), (<|>))
31
import qualified Data.Attoparsec.Text as A
32
import qualified Data.Attoparsec.Combinator as AC
33
import Data.Attoparsec.Text (Parser)
34

  
35
import Ganeti.Parsers
36
import Ganeti.Cpu.Types
37

  
38
-- * Parser implementation
39

  
40
-- | The parser for one line of the CPU status file.
41
oneCPUstatParser :: Parser CPUstat
42
oneCPUstatParser =
43
  let nameP = stringP
44
      userP = numberP
45
      niceP = numberP
46
      systemP = numberP
47
      idleP = numberP
48
      iowaitP = numberP
49
      irqP = numberP
50
      softirqP = numberP
51
      stealP = numberP
52
      guestP = numberP
53
      guest_niceP = numberP
54
  in
55
    CPUstat <$> nameP <*> userP <*> niceP <*> systemP <*> idleP <*> iowaitP
56
            <*> irqP <*> softirqP <*> stealP <*> guestP <*> guest_niceP
57
            <* A.endOfLine
58

  
59
-- | When this is satisfied all the lines containing information about
60
-- the CPU load are parsed.
61
intrFound :: Parser ()
62
intrFound = (A.string "intr" *> return ())
63
             <|> (A.string "page" *> return ())
64
             <|> (A.string "swap" *> return ())
65

  
66
-- | The parser for the fragment of CPU status file containing
67
-- information about the CPU load.
68
cpustatParser :: Parser [CPUstat]
69
cpustatParser = oneCPUstatParser `AC.manyTill` intrFound
b/src/Ganeti/Cpu/Types.hs
1
{-# LANGUAGE TemplateHaskell #-}
2
{-| CPUload data types
3

  
4
This module holds the definition of the data types describing the CPU
5
load according to information collected periodically from @/proc/stat@.
6

  
7
-}
8
{-
9

  
10
Copyright (C) 2013 Google Inc.
11

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

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

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

  
27
-}
28
module Ganeti.Cpu.Types
29
  ( CPUstat(..)
30
  ) where
31

  
32
import Ganeti.THH
33

  
34
-- | This is the format of the data parsed by the input file.
35
$(buildObject "CPUstat" "cs"
36
  [ simpleField "name"       [t| String |]
37
  , simpleField "user"       [t| Int |]
38
  , simpleField "nice"       [t| Int |]
39
  , simpleField "system"     [t| Int |]
40
  , simpleField "idle"       [t| Int |]
41
  , simpleField "iowait"     [t| Int |]
42
  , simpleField "irq"        [t| Int |]
43
  , simpleField "softirq"    [t| Int |]
44
  , simpleField "steal"      [t| Int |]
45
  , simpleField "guest"      [t| Int |]
46
  , simpleField "guest_nice" [t| Int |]
47
  ])

Also available in: Unified diff