0971e647e1fdb6b6148e503a085350528d8f3f0f
[ganeti-local] / test / hs / Test / Ganeti / Storage / Lvm / LVParser.hs
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)"
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)"
59   ]
60
61 -- | Serialize a LVInfo in the same format that is output by @lvs@.
62 serializeLVInfo :: LVInfo -> String
63 serializeLVInfo l = intercalate ";"
64   [ lviUuid l
65   , lviName l
66   , lviAttr l
67   , show $ lviMajor l
68   , show $ lviMinor l
69   , show $ lviKernelMajor l
70   , show $ lviKernelMinor l
71   , show (lviSize l) ++ "B"
72   , show $ lviSegCount l
73   , lviTags l
74   , lviModules l
75   , lviVgUuid l
76   , lviVgName l
77   , lviSegtype l
78   , show (lviSegStart l) ++ "B"
79   , show $ lviSegStartPe l
80   , show (lviSegSize l) ++ "B"
81   , lviSegTags l
82   , lviSegPeRanges l
83   , lviDevices l
84   ] ++ "\n"
85
86 -- | Serialize a list of LVInfo in the same format that is output by @lvs@.
87 serializeLVInfos :: [LVInfo] -> String
88 serializeLVInfos = concatMap serializeLVInfo
89
90 -- | Arbitrary instance for LVInfo.
91 instance Arbitrary LVInfo where
92   arbitrary =
93     LVInfo
94       <$> genUUID        -- uuid
95       <*> genName        -- name
96       <*> genName        -- attr
97       <*> arbitrary      -- major
98       <*> arbitrary      -- minor
99       <*> arbitrary      -- kernel_major
100       <*> arbitrary      -- kernel_minor
101       <*> genNonNegative -- size
102       <*> arbitrary      -- seg_cont
103       <*> genName        -- tags
104       <*> genName        -- modules
105       <*> genUUID        -- vg_uuid
106       <*> genName        -- vg_name
107       <*> genName        -- segtype
108       <*> genNonNegative -- seg_start
109       <*> arbitrary      -- seg_start_pe
110       <*> genNonNegative -- seg_size
111       <*> genName        -- seg_tags
112       <*> genName        -- seg_pe_ranges
113       <*> genName        -- devices
114
115 -- | Test if a randomly generated LV lvs output is properly parsed.
116 prop_parse_lvs_lv :: [LVInfo] -> Property
117 prop_parse_lvs_lv expected =
118   genPropParser lvParser (serializeLVInfos expected) expected
119
120 testSuite "Storage/Lvm/LVParser"
121           [ 'case_lvs_lv,
122             'prop_parse_lvs_lv
123           ]