Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Storage / Diskstats / Parser.hs @ de36f091

History | View | Annotate | Download (2.1 kB)

1 c6bca2d1 Michele Tartara
{-# LANGUAGE OverloadedStrings #-}
2 c6bca2d1 Michele Tartara
{-| Diskstats proc file parser
3 c6bca2d1 Michele Tartara
4 c6bca2d1 Michele Tartara
This module holds the definition of the parser that extracts status
5 c6bca2d1 Michele Tartara
information about the disks of the system from the @/proc/diskstats@ file.
6 c6bca2d1 Michele Tartara
7 c6bca2d1 Michele Tartara
-}
8 c6bca2d1 Michele Tartara
{-
9 c6bca2d1 Michele Tartara
10 c6bca2d1 Michele Tartara
Copyright (C) 2013 Google Inc.
11 c6bca2d1 Michele Tartara
12 c6bca2d1 Michele Tartara
This program is free software; you can redistribute it and/or modify
13 c6bca2d1 Michele Tartara
it under the terms of the GNU General Public License as published by
14 c6bca2d1 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
15 c6bca2d1 Michele Tartara
(at your option) any later version.
16 c6bca2d1 Michele Tartara
17 c6bca2d1 Michele Tartara
This program is distributed in the hope that it will be useful, but
18 c6bca2d1 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
19 c6bca2d1 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 c6bca2d1 Michele Tartara
General Public License for more details.
21 c6bca2d1 Michele Tartara
22 c6bca2d1 Michele Tartara
You should have received a copy of the GNU General Public License
23 c6bca2d1 Michele Tartara
along with this program; if not, write to the Free Software
24 c6bca2d1 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 c6bca2d1 Michele Tartara
02110-1301, USA.
26 c6bca2d1 Michele Tartara
27 c6bca2d1 Michele Tartara
-}
28 c5f6cba2 Helga Velroyen
module Ganeti.Storage.Diskstats.Parser (diskstatsParser) where
29 c6bca2d1 Michele Tartara
30 090e5de8 Spyros Trigazis
import Control.Applicative ((<*>), (<*), (<$>))
31 c6bca2d1 Michele Tartara
import qualified Data.Attoparsec.Text as A
32 c6bca2d1 Michele Tartara
import qualified Data.Attoparsec.Combinator as AC
33 c6bca2d1 Michele Tartara
import Data.Attoparsec.Text (Parser)
34 c6bca2d1 Michele Tartara
35 090e5de8 Spyros Trigazis
import Ganeti.Parsers
36 c5f6cba2 Helga Velroyen
import Ganeti.Storage.Diskstats.Types
37 c6bca2d1 Michele Tartara
38 c6bca2d1 Michele Tartara
-- * Parser implementation
39 c6bca2d1 Michele Tartara
40 c6bca2d1 Michele Tartara
-- | The parser for one line of the diskstatus file.
41 c6bca2d1 Michele Tartara
oneDiskstatsParser :: Parser Diskstats
42 c6bca2d1 Michele Tartara
oneDiskstatsParser =
43 090e5de8 Spyros Trigazis
  let majorP = numberP
44 090e5de8 Spyros Trigazis
      minorP = numberP
45 090e5de8 Spyros Trigazis
      nameP = stringP
46 090e5de8 Spyros Trigazis
      readsNumP = numberP
47 090e5de8 Spyros Trigazis
      mergedReadsP = numberP
48 090e5de8 Spyros Trigazis
      secReadP = numberP
49 090e5de8 Spyros Trigazis
      timeReadP = numberP
50 090e5de8 Spyros Trigazis
      writesP = numberP
51 090e5de8 Spyros Trigazis
      mergedWritesP = numberP
52 090e5de8 Spyros Trigazis
      secWrittenP = numberP
53 090e5de8 Spyros Trigazis
      timeWriteP = numberP
54 090e5de8 Spyros Trigazis
      iosP = numberP
55 090e5de8 Spyros Trigazis
      timeIOP = numberP
56 090e5de8 Spyros Trigazis
      wIOmillisP = numberP
57 090e5de8 Spyros Trigazis
  in
58 090e5de8 Spyros Trigazis
    Diskstats <$> majorP <*> minorP <*> nameP <*> readsNumP <*> mergedReadsP
59 090e5de8 Spyros Trigazis
      <*> secReadP <*> timeReadP <*> writesP <*> mergedWritesP <*> secWrittenP
60 090e5de8 Spyros Trigazis
      <*> timeWriteP <*> iosP <*> timeIOP <*> wIOmillisP <* A.endOfLine
61 c6bca2d1 Michele Tartara
62 c6bca2d1 Michele Tartara
-- | The parser for a whole diskstatus file.
63 c6bca2d1 Michele Tartara
diskstatsParser :: Parser [Diskstats]
64 c6bca2d1 Michele Tartara
diskstatsParser = oneDiskstatsParser `AC.manyTill` A.endOfInput