Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Objects.hs @ 61899e64

History | View | Annotate | Download (7.6 kB)

1 9924d61e Iustin Pop
{-# LANGUAGE TemplateHaskell, TypeSynonymInstances, FlexibleInstances #-}
2 e5a29b6c Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e5a29b6c Iustin Pop
4 e5a29b6c Iustin Pop
{-| Unittests for ganeti-htools.
5 e5a29b6c Iustin Pop
6 e5a29b6c Iustin Pop
-}
7 e5a29b6c Iustin Pop
8 e5a29b6c Iustin Pop
{-
9 e5a29b6c Iustin Pop
10 e5a29b6c Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e5a29b6c Iustin Pop
12 e5a29b6c Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e5a29b6c Iustin Pop
it under the terms of the GNU General Public License as published by
14 e5a29b6c Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e5a29b6c Iustin Pop
(at your option) any later version.
16 e5a29b6c Iustin Pop
17 e5a29b6c Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e5a29b6c Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e5a29b6c Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e5a29b6c Iustin Pop
General Public License for more details.
21 e5a29b6c Iustin Pop
22 e5a29b6c Iustin Pop
You should have received a copy of the GNU General Public License
23 e5a29b6c Iustin Pop
along with this program; if not, write to the Free Software
24 e5a29b6c Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e5a29b6c Iustin Pop
02110-1301, USA.
26 e5a29b6c Iustin Pop
27 e5a29b6c Iustin Pop
-}
28 e5a29b6c Iustin Pop
29 305e174c Iustin Pop
module Test.Ganeti.Objects
30 305e174c Iustin Pop
  ( testObjects
31 8d2b6a12 Iustin Pop
  , Hypervisor(..)
32 8d2b6a12 Iustin Pop
  , Node(..)
33 9924d61e Iustin Pop
  , genEmptyCluster
34 305e174c Iustin Pop
  ) where
35 e5a29b6c Iustin Pop
36 8d2b6a12 Iustin Pop
import Test.QuickCheck
37 8d2b6a12 Iustin Pop
38 305e174c Iustin Pop
import Control.Applicative
39 e5a29b6c Iustin Pop
import qualified Data.Map as Map
40 305e174c Iustin Pop
import qualified Data.Set as Set
41 e5a29b6c Iustin Pop
42 e5a29b6c Iustin Pop
import Test.Ganeti.TestHelper
43 305e174c Iustin Pop
import Test.Ganeti.TestCommon
44 9924d61e Iustin Pop
45 9924d61e Iustin Pop
import qualified Ganeti.Constants as C
46 8d2b6a12 Iustin Pop
import Ganeti.Objects as Objects
47 ce93b4a0 Iustin Pop
import Ganeti.JSON
48 8d2b6a12 Iustin Pop
49 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
50 5b11f8db Iustin Pop
51 8d2b6a12 Iustin Pop
-- * Arbitrary instances
52 e5a29b6c Iustin Pop
53 7022db83 Iustin Pop
$(genArbitrary ''Hypervisor)
54 305e174c Iustin Pop
55 7022db83 Iustin Pop
$(genArbitrary ''PartialNDParams)
56 305e174c Iustin Pop
57 8d2b6a12 Iustin Pop
instance Arbitrary Node where
58 8d2b6a12 Iustin Pop
  arbitrary = Node <$> getFQDN <*> getFQDN <*> getFQDN
59 305e174c Iustin Pop
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
60 305e174c Iustin Pop
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
61 305e174c Iustin Pop
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
62 305e174c Iustin Pop
              <*> (Set.fromList <$> genTags)
63 305e174c Iustin Pop
64 7022db83 Iustin Pop
$(genArbitrary ''FileDriver)
65 8d2b6a12 Iustin Pop
66 7022db83 Iustin Pop
$(genArbitrary ''BlockDriver)
67 8d2b6a12 Iustin Pop
68 7022db83 Iustin Pop
$(genArbitrary ''DiskMode)
69 8d2b6a12 Iustin Pop
70 8d2b6a12 Iustin Pop
instance Arbitrary DiskLogicalId where
71 8d2b6a12 Iustin Pop
  arbitrary = oneof [ LIDPlain <$> arbitrary <*> arbitrary
72 8d2b6a12 Iustin Pop
                    , LIDDrbd8 <$> getFQDN <*> getFQDN <*> arbitrary
73 8d2b6a12 Iustin Pop
                               <*> arbitrary <*> arbitrary <*> arbitrary
74 8d2b6a12 Iustin Pop
                    , LIDFile  <$> arbitrary <*> arbitrary
75 8d2b6a12 Iustin Pop
                    , LIDBlockDev <$> arbitrary <*> arbitrary
76 8d2b6a12 Iustin Pop
                    , LIDRados <$> arbitrary <*> arbitrary
77 8d2b6a12 Iustin Pop
                    ]
78 8d2b6a12 Iustin Pop
79 8d2b6a12 Iustin Pop
-- | 'Disk' 'arbitrary' instance. Since we don't test disk hierarchy
80 8d2b6a12 Iustin Pop
-- properties, we only generate disks with no children (FIXME), as
81 8d2b6a12 Iustin Pop
-- generating recursive datastructures is a bit more work.
82 8d2b6a12 Iustin Pop
instance Arbitrary Disk where
83 5b11f8db Iustin Pop
  arbitrary = Disk <$> arbitrary <*> pure [] <*> arbitrary
84 8d2b6a12 Iustin Pop
                   <*> arbitrary <*> arbitrary
85 8d2b6a12 Iustin Pop
86 7022db83 Iustin Pop
-- FIXME: we should generate proper values, >=0, etc., but this is
87 7022db83 Iustin Pop
-- hard for partial ones, where all must be wrapped in a 'Maybe'
88 7022db83 Iustin Pop
$(genArbitrary ''PartialBeParams)
89 ce93b4a0 Iustin Pop
90 7022db83 Iustin Pop
$(genArbitrary ''DiskTemplate)
91 ce93b4a0 Iustin Pop
92 7022db83 Iustin Pop
$(genArbitrary ''AdminState)
93 ce93b4a0 Iustin Pop
94 7022db83 Iustin Pop
$(genArbitrary ''NICMode)
95 ce93b4a0 Iustin Pop
96 7022db83 Iustin Pop
$(genArbitrary ''PartialNicParams)
97 ce93b4a0 Iustin Pop
98 7022db83 Iustin Pop
$(genArbitrary ''PartialNic)
99 ce93b4a0 Iustin Pop
100 ce93b4a0 Iustin Pop
instance Arbitrary Instance where
101 ce93b4a0 Iustin Pop
  arbitrary =
102 ce93b4a0 Iustin Pop
    Instance
103 ce93b4a0 Iustin Pop
      <$> getFQDN <*> getFQDN <*> getFQDN -- OS name, but...
104 ce93b4a0 Iustin Pop
      <*> arbitrary
105 ce93b4a0 Iustin Pop
      -- FIXME: add non-empty hvparams when they're a proper type
106 5b11f8db Iustin Pop
      <*> pure (Container Map.empty) <*> arbitrary
107 ce93b4a0 Iustin Pop
      -- ... and for OSParams
108 5b11f8db Iustin Pop
      <*> pure (Container Map.empty) <*> arbitrary <*> arbitrary
109 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary <*> arbitrary
110 ce93b4a0 Iustin Pop
      -- ts
111 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary
112 ce93b4a0 Iustin Pop
      -- uuid
113 ce93b4a0 Iustin Pop
      <*> arbitrary
114 ce93b4a0 Iustin Pop
      -- serial
115 ce93b4a0 Iustin Pop
      <*> arbitrary
116 ce93b4a0 Iustin Pop
      -- tags
117 ce93b4a0 Iustin Pop
      <*> (Set.fromList <$> genTags)
118 ce93b4a0 Iustin Pop
119 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
120 9924d61e Iustin Pop
-- validation rules.
121 9924d61e Iustin Pop
$(genArbitrary ''PartialISpecParams)
122 9924d61e Iustin Pop
123 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
124 9924d61e Iustin Pop
-- validation rules.
125 9924d61e Iustin Pop
$(genArbitrary ''PartialIPolicy)
126 9924d61e Iustin Pop
127 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
128 9924d61e Iustin Pop
-- validation rules.
129 9924d61e Iustin Pop
instance Arbitrary NodeGroup where
130 9924d61e Iustin Pop
  arbitrary = NodeGroup <$> getFQDN <*> pure [] <*> arbitrary <*> arbitrary
131 5b11f8db Iustin Pop
                        <*> arbitrary <*> pure (Container Map.empty)
132 9924d61e Iustin Pop
                        -- ts
133 9924d61e Iustin Pop
                        <*> arbitrary <*> arbitrary
134 9924d61e Iustin Pop
                        -- uuid
135 9924d61e Iustin Pop
                        <*> arbitrary
136 9924d61e Iustin Pop
                        -- serial
137 9924d61e Iustin Pop
                        <*> arbitrary
138 9924d61e Iustin Pop
                        -- tags
139 9924d61e Iustin Pop
                        <*> (Set.fromList <$> genTags)
140 9924d61e Iustin Pop
141 9924d61e Iustin Pop
$(genArbitrary ''AllocPolicy)
142 9924d61e Iustin Pop
$(genArbitrary ''FilledISpecParams)
143 9924d61e Iustin Pop
$(genArbitrary ''FilledIPolicy)
144 9924d61e Iustin Pop
$(genArbitrary ''IpFamily)
145 9924d61e Iustin Pop
$(genArbitrary ''FilledNDParams)
146 9924d61e Iustin Pop
$(genArbitrary ''FilledNicParams)
147 9924d61e Iustin Pop
$(genArbitrary ''FilledBeParams)
148 9924d61e Iustin Pop
149 9924d61e Iustin Pop
-- | No real arbitrary instance for 'ClusterHvParams' yet.
150 9924d61e Iustin Pop
instance Arbitrary ClusterHvParams where
151 9924d61e Iustin Pop
  arbitrary = return $ Container Map.empty
152 9924d61e Iustin Pop
153 9924d61e Iustin Pop
-- | No real arbitrary instance for 'OsHvParams' yet.
154 9924d61e Iustin Pop
instance Arbitrary OsHvParams where
155 9924d61e Iustin Pop
  arbitrary = return $ Container Map.empty
156 9924d61e Iustin Pop
157 9924d61e Iustin Pop
instance Arbitrary ClusterNicParams where
158 9924d61e Iustin Pop
  arbitrary = (Container . Map.singleton C.ppDefault) <$> arbitrary
159 9924d61e Iustin Pop
160 9924d61e Iustin Pop
instance Arbitrary OsParams where
161 9924d61e Iustin Pop
  arbitrary = (Container . Map.fromList) <$> arbitrary
162 9924d61e Iustin Pop
163 9924d61e Iustin Pop
instance Arbitrary ClusterOsParams where
164 9924d61e Iustin Pop
  arbitrary = (Container . Map.fromList) <$> arbitrary
165 9924d61e Iustin Pop
166 9924d61e Iustin Pop
instance Arbitrary ClusterBeParams where
167 9924d61e Iustin Pop
  arbitrary = (Container . Map.fromList) <$> arbitrary
168 9924d61e Iustin Pop
169 9924d61e Iustin Pop
instance Arbitrary TagSet where
170 9924d61e Iustin Pop
  arbitrary = Set.fromList <$> genTags
171 9924d61e Iustin Pop
172 9924d61e Iustin Pop
$(genArbitrary ''Cluster)
173 9924d61e Iustin Pop
174 9924d61e Iustin Pop
-- | Generator for config data with an empty cluster (no instances),
175 9924d61e Iustin Pop
-- with N defined nodes.
176 9924d61e Iustin Pop
genEmptyCluster :: Int -> Gen ConfigData
177 9924d61e Iustin Pop
genEmptyCluster ncount = do
178 9924d61e Iustin Pop
  nodes <- vector ncount
179 9924d61e Iustin Pop
  version <- arbitrary
180 9924d61e Iustin Pop
  let guuid = "00"
181 b9bdc10e Iustin Pop
      nodes' = zipWith (\n idx -> n { nodeGroup = guuid,
182 b9bdc10e Iustin Pop
                                      nodeName = nodeName n ++ show idx })
183 b9bdc10e Iustin Pop
               nodes [(1::Int)..]
184 9924d61e Iustin Pop
      contnodes = Container . Map.fromList $ map (\n -> (nodeName n, n)) nodes'
185 5b11f8db Iustin Pop
      continsts = Container Map.empty
186 9924d61e Iustin Pop
  grp <- arbitrary
187 9924d61e Iustin Pop
  let contgroups = Container $ Map.singleton guuid grp
188 9924d61e Iustin Pop
  serial <- arbitrary
189 c3a8e06d Iustin Pop
  cluster <- resize 8 arbitrary
190 9924d61e Iustin Pop
  let c = ConfigData version cluster contnodes contgroups continsts serial
191 9924d61e Iustin Pop
  return c
192 9924d61e Iustin Pop
193 8d2b6a12 Iustin Pop
-- * Test properties
194 8d2b6a12 Iustin Pop
195 e5a29b6c Iustin Pop
-- | Tests that fillDict behaves correctly
196 20bc5360 Iustin Pop
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
197 20bc5360 Iustin Pop
prop_fillDict defaults custom =
198 e5a29b6c Iustin Pop
  let d_map = Map.fromList defaults
199 e5a29b6c Iustin Pop
      d_keys = map fst defaults
200 e5a29b6c Iustin Pop
      c_map = Map.fromList custom
201 e5a29b6c Iustin Pop
      c_keys = map fst custom
202 942a9a6a Iustin Pop
  in conjoin [ printTestCase "Empty custom filling"
203 942a9a6a Iustin Pop
               (fillDict d_map Map.empty [] == d_map)
204 942a9a6a Iustin Pop
             , printTestCase "Empty defaults filling"
205 942a9a6a Iustin Pop
               (fillDict Map.empty c_map [] == c_map)
206 942a9a6a Iustin Pop
             , printTestCase "Delete all keys"
207 942a9a6a Iustin Pop
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
208 942a9a6a Iustin Pop
             ]
209 8d2b6a12 Iustin Pop
210 8d2b6a12 Iustin Pop
-- | Test that the serialisation of 'DiskLogicalId', which is
211 8d2b6a12 Iustin Pop
-- implemented manually, is idempotent. Since we don't have a
212 8d2b6a12 Iustin Pop
-- standalone JSON instance for DiskLogicalId (it's a data type that
213 8d2b6a12 Iustin Pop
-- expands over two fields in a JSObject), we test this by actially
214 8d2b6a12 Iustin Pop
-- testing entire Disk serialisations. So this tests two things at
215 8d2b6a12 Iustin Pop
-- once, basically.
216 8d2b6a12 Iustin Pop
prop_Disk_serialisation :: Disk -> Property
217 63b068c1 Iustin Pop
prop_Disk_serialisation = testSerialisation
218 8d2b6a12 Iustin Pop
219 8d2b6a12 Iustin Pop
-- | Check that node serialisation is idempotent.
220 8d2b6a12 Iustin Pop
prop_Node_serialisation :: Node -> Property
221 63b068c1 Iustin Pop
prop_Node_serialisation = testSerialisation
222 e5a29b6c Iustin Pop
223 ce93b4a0 Iustin Pop
-- | Check that instance serialisation is idempotent.
224 ce93b4a0 Iustin Pop
prop_Inst_serialisation :: Instance -> Property
225 ce93b4a0 Iustin Pop
prop_Inst_serialisation = testSerialisation
226 ce93b4a0 Iustin Pop
227 9924d61e Iustin Pop
-- | Check config serialisation.
228 9924d61e Iustin Pop
prop_Config_serialisation :: Property
229 9924d61e Iustin Pop
prop_Config_serialisation =
230 c3a8e06d Iustin Pop
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
231 9924d61e Iustin Pop
232 e5a29b6c Iustin Pop
testSuite "Objects"
233 20bc5360 Iustin Pop
  [ 'prop_fillDict
234 8d2b6a12 Iustin Pop
  , 'prop_Disk_serialisation
235 ce93b4a0 Iustin Pop
  , 'prop_Inst_serialisation
236 8d2b6a12 Iustin Pop
  , 'prop_Node_serialisation
237 44be51aa Iustin Pop
  , 'prop_Config_serialisation
238 9924d61e Iustin Pop
  ]