Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Storage / Lvm / LVParser.hs @ bdf51a05

History | View | Annotate | Download (3.6 kB)

1
{-# LANGUAGE OverloadedStrings #-}
2
{-| Logical Volumer information parser
3

    
4
This module holds the definition of the parser that extracts status
5
information about the logical volumes (LVs) of the system from the output of the
6
@lvs@ command.
7

    
8
-}
9
{-
10

    
11
Copyright (C) 2013 Google Inc.
12

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

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

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

    
28
-}
29
module Ganeti.Storage.Lvm.LVParser (lvParser, lvCommand) where
30

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

    
37
import Ganeti.Storage.Lvm.Types
38

    
39

    
40
-- | The separator of the fields returned by @lvs@
41
lvsSeparator :: Char
42
lvsSeparator = ';'
43

    
44
-- * Utility functions
45

    
46
-- | Our own space-skipping function, because A.skipSpace also skips
47
-- newline characters. It skips ZERO or more spaces, so it does not
48
-- fail if there are no spaces.
49
skipSpaces :: Parser ()
50
skipSpaces = A.skipWhile A.isHorizontalSpace
51

    
52
-- | A parser recognizing a number of bytes, represented as a number preceeded
53
-- by a separator and followed by the "B" character.
54
bytesP :: Parser Int
55
bytesP = A.char lvsSeparator *> A.decimal <* A.char 'B'
56

    
57
-- | A parser recognizing a number discarding the preceeding separator
58
intP :: Parser Int
59
intP = A.char lvsSeparator *> A.signed A.decimal
60

    
61
-- | A parser recognizing a string starting with and closed by a separator (both
62
-- are discarded)
63
stringP :: Parser String
64
stringP =
65
  A.char lvsSeparator *> fmap unpack (A.takeWhile (`notElem`
66
    [ lvsSeparator
67
    , '\n']
68
    ))
69

    
70
-- * Parser implementation
71

    
72
-- | The command providing the data, in the format the parser expects
73
lvCommand :: [String]
74
lvCommand =
75
  [ "lvs"
76
  , "--noheadings"
77
  , "--units B"
78
  , "-- separator ;"
79
  , "-o lv_uuid,lv_name,lv_attr,lv_major,lv_minor,lv_kernel_major\
80
    \,lv_kernel_minor,lv_size,seg_count,lv_tags,modules,vg_uuid,vg_name,segtype\
81
    \,seg_start,seg_start_pe,seg_size,seg_tags,seg_pe_ranges,devices"
82
  ]
83

    
84
-- | The parser for one line of the diskstatus file.
85
oneLvParser :: Parser LVInfo
86
oneLvParser =
87
  let uuidP = skipSpaces *> fmap unpack (A.takeWhile (/= lvsSeparator))
88
      nameP = stringP
89
      attrP = stringP
90
      majorP = intP
91
      minorP = intP
92
      kernelMajorP = intP
93
      kernelMinorP = intP
94
      sizeP = bytesP
95
      segCountP = intP
96
      tagsP = stringP
97
      modulesP = stringP
98
      vgUuidP = stringP
99
      vgNameP = stringP
100
      segtypeP = stringP
101
      segStartP = bytesP
102
      segStartPeP = intP
103
      segSizeP = bytesP
104
      segTagsP = stringP
105
      segPeRangesP = stringP
106
      devicesP = stringP
107
    in
108
      LVInfo
109
        <$> uuidP <*> nameP <*> attrP <*> majorP <*> minorP <*> kernelMajorP
110
        <*> kernelMinorP <*> sizeP <*> segCountP <*> tagsP <*> modulesP
111
        <*> vgUuidP <*> vgNameP <*> segtypeP <*> segStartP <*> segStartPeP
112
        <*> segSizeP <*> segTagsP <*> segPeRangesP <*> devicesP <* A.endOfLine
113

    
114
-- | The parser for a whole diskstatus file.
115
lvParser :: Parser [LVInfo]
116
lvParser = oneLvParser `AC.manyTill` A.endOfInput