Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Storage / Lvm / LVParser.hs @ 58458012

History | View | Annotate | Download (4.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for the LV Parser -}
5

    
6
{-
7

    
8
Copyright (C) 2013 Google Inc.
9

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

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

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

    
25
-}
26

    
27
module Test.Ganeti.Storage.Lvm.LVParser (testStorage_Lvm_LVParser) where
28

    
29
import Test.QuickCheck as QuickCheck hiding (Result)
30
import Test.HUnit
31

    
32
import Test.Ganeti.TestHelper
33
import Test.Ganeti.TestCommon
34

    
35
import Control.Applicative ((<$>), (<*>))
36
import Data.List (intercalate)
37

    
38
import Ganeti.Storage.Lvm.LVParser
39
import Ganeti.Storage.Lvm.Types
40

    
41
{-# ANN module "HLint: ignore Use camelCase" #-}
42

    
43

    
44
-- | Test parsing a LV @lvs@ output.
45
case_lvs_lv :: Assertion
46
case_lvs_lv = testParser lvParser "lvs_lv.txt"
47
  [ LVInfo "nhasjL-cnZi-uqLS-WRLj-tkXI-nvCB-n0o2lj"
48
      "df9ff3f6-a833-48ff-8bd5-bff2eaeab759.disk0_data" "-wi-ao" (negate 1)
49
      (negate 1) 253 0 1073741824 1
50
      "originstname+instance1.example.com" ""
51
      "uZgXit-eiRr-vRqe-xpEo-e9nU-mTuR-9nfVIU" "xenvg" "linear" 0 0 1073741824
52
      "" "/dev/sda5:0-15" "/dev/sda5(0)" Nothing
53
  , LVInfo "5fW5mE-SBSs-GSU0-KZDg-hnwb-sZOC-zZt736"
54
      "df9ff3f6-a833-48ff-8bd5-bff2eaeab759.disk0_meta" "-wi-ao" (negate 1)
55
      (negate 1) 253 1 134217728 1
56
      "originstname+instance1.example.com" ""
57
      "uZgXit-eiRr-vRqe-xpEo-e9nU-mTuR-9nfVIU" "xenvg" "linear" 0 0 134217728 ""
58
      "/dev/sda5:16-17" "/dev/sda5(16)" Nothing
59
  ]
60

    
61
-- | Serialize a LVInfo in the same format that is output by @lvs@.
62
-- The "instance" field is not serialized because it's not provided by @lvs@
63
-- so it is not part of this test.
64
serializeLVInfo :: LVInfo -> String
65
serializeLVInfo l = intercalate ";"
66
  [ lviUuid l
67
  , lviName l
68
  , lviAttr l
69
  , show $ lviMajor l
70
  , show $ lviMinor l
71
  , show $ lviKernelMajor l
72
  , show $ lviKernelMinor l
73
  , show (lviSize l) ++ "B"
74
  , show $ lviSegCount l
75
  , lviTags l
76
  , lviModules l
77
  , lviVgUuid l
78
  , lviVgName l
79
  , lviSegtype l
80
  , show (lviSegStart l) ++ "B"
81
  , show $ lviSegStartPe l
82
  , show (lviSegSize l) ++ "B"
83
  , lviSegTags l
84
  , lviSegPeRanges l
85
  , lviDevices l
86
  ] ++ "\n"
87

    
88
-- | Serialize a list of LVInfo in the same format that is output by @lvs@.
89
serializeLVInfos :: [LVInfo] -> String
90
serializeLVInfos = concatMap serializeLVInfo
91

    
92
-- | Arbitrary instance for LVInfo.
93
-- The instance is always Nothing because it is not part of the parsed data:
94
-- it is added afterwards from a different source.
95
instance Arbitrary LVInfo where
96
  arbitrary =
97
    LVInfo
98
      <$> genUUID        -- uuid
99
      <*> genName        -- name
100
      <*> genName        -- attr
101
      <*> arbitrary      -- major
102
      <*> arbitrary      -- minor
103
      <*> arbitrary      -- kernel_major
104
      <*> arbitrary      -- kernel_minor
105
      <*> genNonNegative -- size
106
      <*> arbitrary      -- seg_cont
107
      <*> genName        -- tags
108
      <*> genName        -- modules
109
      <*> genUUID        -- vg_uuid
110
      <*> genName        -- vg_name
111
      <*> genName        -- segtype
112
      <*> genNonNegative -- seg_start
113
      <*> arbitrary      -- seg_start_pe
114
      <*> genNonNegative -- seg_size
115
      <*> genName        -- seg_tags
116
      <*> genName        -- seg_pe_ranges
117
      <*> genName        -- devices
118
      <*> return Nothing -- instance
119

    
120
-- | Test if a randomly generated LV lvs output is properly parsed.
121
prop_parse_lvs_lv :: [LVInfo] -> Property
122
prop_parse_lvs_lv expected =
123
  genPropParser lvParser (serializeLVInfos expected) expected
124

    
125
testSuite "Storage/Lvm/LVParser"
126
          [ 'case_lvs_lv,
127
            'prop_parse_lvs_lv
128
          ]