Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 37696594

History | View | Annotate | Download (14.1 kB)

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

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11

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

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

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

    
27
-}
28

    
29
module Test.Ganeti.Objects
30
  ( testObjects
31
  , Node(..)
32
  , genEmptyCluster
33
  , genValidNetwork
34
  , genBitStringMaxLen
35
  ) where
36

    
37
import Test.QuickCheck
38
import qualified Test.HUnit as HUnit
39

    
40
import Control.Applicative
41
import Control.Monad
42
import Data.Char
43
import qualified Data.Map as Map
44
import qualified Data.Set as Set
45
import qualified Text.JSON as J
46

    
47
import Test.Ganeti.TestHelper
48
import Test.Ganeti.TestCommon
49
import Test.Ganeti.Types ()
50

    
51
import qualified Ganeti.Constants as C
52
import Ganeti.Network
53
import Ganeti.Objects as Objects
54
import Ganeti.JSON
55
import Ganeti.Types
56

    
57
{-# ANN module "HLint: ignore Use camelCase" #-}
58

    
59
-- * Arbitrary instances
60

    
61
$(genArbitrary ''PartialNDParams)
62

    
63
instance Arbitrary Node where
64
  arbitrary = Node <$> genFQDN <*> genFQDN <*> genFQDN
65
              <*> arbitrary <*> arbitrary <*> arbitrary <*> genFQDN
66
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
67
              <*> arbitrary <*> arbitrary <*> genFQDN <*> arbitrary
68
              <*> (Set.fromList <$> genTags)
69

    
70
$(genArbitrary ''BlockDriver)
71

    
72
$(genArbitrary ''DiskMode)
73

    
74
instance Arbitrary DiskLogicalId where
75
  arbitrary = oneof [ LIDPlain <$> arbitrary <*> arbitrary
76
                    , LIDDrbd8 <$> genFQDN <*> genFQDN <*> arbitrary
77
                               <*> arbitrary <*> arbitrary <*> arbitrary
78
                    , LIDFile  <$> arbitrary <*> arbitrary
79
                    , LIDBlockDev <$> arbitrary <*> arbitrary
80
                    , LIDRados <$> arbitrary <*> arbitrary
81
                    ]
82

    
83
-- | 'Disk' 'arbitrary' instance. Since we don't test disk hierarchy
84
-- properties, we only generate disks with no children (FIXME), as
85
-- generating recursive datastructures is a bit more work.
86
instance Arbitrary Disk where
87
  arbitrary = Disk <$> arbitrary <*> pure [] <*> arbitrary
88
                   <*> arbitrary <*> arbitrary
89

    
90
-- FIXME: we should generate proper values, >=0, etc., but this is
91
-- hard for partial ones, where all must be wrapped in a 'Maybe'
92
$(genArbitrary ''PartialBeParams)
93

    
94
$(genArbitrary ''AdminState)
95

    
96
$(genArbitrary ''PartialNicParams)
97

    
98
$(genArbitrary ''PartialNic)
99

    
100
instance Arbitrary Instance where
101
  arbitrary =
102
    Instance
103
      <$> genFQDN <*> genFQDN <*> genFQDN -- OS name, but...
104
      <*> arbitrary
105
      -- FIXME: add non-empty hvparams when they're a proper type
106
      <*> pure (GenericContainer Map.empty) <*> arbitrary
107
      -- ... and for OSParams
108
      <*> pure (GenericContainer Map.empty) <*> arbitrary <*> arbitrary
109
      <*> arbitrary <*> arbitrary <*> arbitrary
110
      -- ts
111
      <*> arbitrary <*> arbitrary
112
      -- uuid
113
      <*> arbitrary
114
      -- serial
115
      <*> arbitrary
116
      -- tags
117
      <*> (Set.fromList <$> genTags)
118

    
119
-- | FIXME: This generates completely random data, without normal
120
-- validation rules.
121
$(genArbitrary ''PartialISpecParams)
122

    
123
-- | FIXME: This generates completely random data, without normal
124
-- validation rules.
125
$(genArbitrary ''PartialIPolicy)
126

    
127
$(genArbitrary ''FilledISpecParams)
128
$(genArbitrary ''FilledIPolicy)
129
$(genArbitrary ''IpFamily)
130
$(genArbitrary ''FilledNDParams)
131
$(genArbitrary ''FilledNicParams)
132
$(genArbitrary ''FilledBeParams)
133

    
134
-- | No real arbitrary instance for 'ClusterHvParams' yet.
135
instance Arbitrary ClusterHvParams where
136
  arbitrary = return $ GenericContainer Map.empty
137

    
138
-- | No real arbitrary instance for 'OsHvParams' yet.
139
instance Arbitrary OsHvParams where
140
  arbitrary = return $ GenericContainer Map.empty
141

    
142
instance Arbitrary ClusterNicParams where
143
  arbitrary = (GenericContainer . Map.singleton C.ppDefault) <$> arbitrary
144

    
145
instance Arbitrary OsParams where
146
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
147

    
148
instance Arbitrary ClusterOsParams where
149
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
150

    
151
instance Arbitrary ClusterBeParams where
152
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
153

    
154
instance Arbitrary TagSet where
155
  arbitrary = Set.fromList <$> genTags
156

    
157
$(genArbitrary ''Cluster)
158

    
159
instance Arbitrary Network where
160
  arbitrary = genValidNetwork
161

    
162
-- | Generates a network instance with minimum netmasks of /24. Generating
163
-- bigger networks slows down the tests, because long bit strings are generated
164
-- for the reservations.
165
genValidNetwork :: Gen Objects.Network
166
genValidNetwork = do
167
  -- generate netmask for the IPv4 network
168
  netmask <- choose (24::Int, 30)
169
  name <- genName >>= mkNonEmpty
170
  mac_prefix <- genMaybe genName
171
  net <- genIp4NetWithNetmask netmask
172
  net6 <- genMaybe genIp6Net
173
  -- gateway <- genMaybe genIp4AddrStr
174
  -- gateway6 <- genMaybe genIp6Addr
175
  let gateway = Nothing
176
  let gateway6 = Nothing
177
  res <- liftM Just (genBitString $ netmask2NumHosts netmask)
178
  ext_res <- liftM Just (genZeroedBitString $ netmask2NumHosts netmask)
179
  let n = Network name mac_prefix net net6 gateway
180
          gateway6 res ext_res 0 Set.empty
181
  return n
182

    
183
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
184
genBitString :: Int -> Gen String
185
genBitString len = vectorOf len (elements "01")
186

    
187
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
188
genZeroedBitString :: Int -> Gen String
189
genZeroedBitString len = vectorOf len (elements "0")
190

    
191
-- | Generate an arbitrary string consisting of '0' and '1' of the maximum given
192
-- length.
193
genBitStringMaxLen :: Int -> Gen String
194
genBitStringMaxLen maxLen = choose (0, maxLen) >>= genBitString
195

    
196
-- | Generator for config data with an empty cluster (no instances),
197
-- with N defined nodes.
198
genEmptyCluster :: Int -> Gen ConfigData
199
genEmptyCluster ncount = do
200
  nodes <- vector ncount
201
  version <- arbitrary
202
  let guuid = "00"
203
      nodes' = zipWith (\n idx ->
204
                          let newname = nodeName n ++ "-" ++ show idx
205
                          in (newname, n { nodeGroup = guuid,
206
                                           nodeName = newname}))
207
               nodes [(1::Int)..]
208
      nodemap = Map.fromList nodes'
209
      contnodes = if Map.size nodemap /= ncount
210
                    then error ("Inconsistent node map, duplicates in" ++
211
                                " node name list? Names: " ++
212
                                show (map fst nodes'))
213
                    else GenericContainer nodemap
214
      continsts = GenericContainer Map.empty
215
  grp <- arbitrary
216
  let contgroups = GenericContainer $ Map.singleton guuid grp
217
  serial <- arbitrary
218
  cluster <- resize 8 arbitrary
219
  let c = ConfigData version cluster contnodes contgroups continsts serial
220
  return c
221

    
222
-- * Test properties
223

    
224
-- | Tests that fillDict behaves correctly
225
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
226
prop_fillDict defaults custom =
227
  let d_map = Map.fromList defaults
228
      d_keys = map fst defaults
229
      c_map = Map.fromList custom
230
      c_keys = map fst custom
231
  in conjoin [ printTestCase "Empty custom filling"
232
               (fillDict d_map Map.empty [] == d_map)
233
             , printTestCase "Empty defaults filling"
234
               (fillDict Map.empty c_map [] == c_map)
235
             , printTestCase "Delete all keys"
236
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
237
             ]
238

    
239
-- | Test that the serialisation of 'DiskLogicalId', which is
240
-- implemented manually, is idempotent. Since we don't have a
241
-- standalone JSON instance for DiskLogicalId (it's a data type that
242
-- expands over two fields in a JSObject), we test this by actially
243
-- testing entire Disk serialisations. So this tests two things at
244
-- once, basically.
245
prop_Disk_serialisation :: Disk -> Property
246
prop_Disk_serialisation = testSerialisation
247

    
248
-- | Check that node serialisation is idempotent.
249
prop_Node_serialisation :: Node -> Property
250
prop_Node_serialisation = testSerialisation
251

    
252
-- | Check that instance serialisation is idempotent.
253
prop_Inst_serialisation :: Instance -> Property
254
prop_Inst_serialisation = testSerialisation
255

    
256
-- | Check that network serialisation is idempotent.
257
prop_Network_serialisation :: Network -> Property
258
prop_Network_serialisation = testSerialisation
259

    
260
-- | Check config serialisation.
261
prop_Config_serialisation :: Property
262
prop_Config_serialisation =
263
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
264

    
265
-- | Custom HUnit test to check the correspondence between Haskell-generated
266
-- networks and their Python decoded, validated and re-encoded version.
267
-- For the technical background of this unit test, check the documentation
268
-- of "case_py_compat_types" of test/hs/Test/Ganeti/Opcodes.hs
269
case_py_compat_networks :: HUnit.Assertion
270
case_py_compat_networks = do
271
  let num_networks = 500::Int
272
  networks <- genSample (vectorOf num_networks genValidNetwork)
273
  let networks_with_properties = map getNetworkProperties networks
274
      serialized = J.encode networks
275
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
276
  mapM_ (\net -> when (any (not . isAscii) (J.encode net)) .
277
                 HUnit.assertFailure $
278
                 "Network has non-ASCII fields: " ++ show net
279
        ) networks
280
  py_stdout <-
281
    runPython "from ganeti import network\n\
282
              \from ganeti import objects\n\
283
              \from ganeti import serializer\n\
284
              \import sys\n\
285
              \net_data = serializer.Load(sys.stdin.read())\n\
286
              \decoded = [objects.Network.FromDict(n) for n in net_data]\n\
287
              \encoded = []\n\
288
              \for net in decoded:\n\
289
              \  a = network.AddressPool(net)\n\
290
              \  encoded.append((a._GetFreeCount(), a._GetReservedCount(), \\\n\
291
              \    net.ToDict()))\n\
292
              \print serializer.Dump(encoded)" serialized
293
    >>= checkPythonResult
294
  let deserialised = J.decode py_stdout::J.Result [(Int, Int, Network)]
295
  decoded <- case deserialised of
296
               J.Ok ops -> return ops
297
               J.Error msg ->
298
                 HUnit.assertFailure ("Unable to decode networks: " ++ msg)
299
                 -- this already raised an expection, but we need it
300
                 -- for proper types
301
                 >> fail "Unable to decode networks"
302
  HUnit.assertEqual "Mismatch in number of returned networks"
303
    (length decoded) (length networks_with_properties)
304
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
305
        ) $ zip decoded networks_with_properties
306

    
307
-- | Creates a tuple of the given network combined with some of its properties
308
-- to be compared against the same properties generated by the python code.
309
getNetworkProperties :: Network -> (Int, Int, Network)
310
getNetworkProperties net =
311
  let maybePool = createAddressPool net
312
  in  case maybePool of
313
           (Just pool) -> (getFreeCount pool, getReservedCount pool, net)
314
           Nothing -> (-1, -1, net)
315

    
316
-- | Tests the compatibility between Haskell-serialized node groups and their
317
-- python-decoded and encoded version.
318
case_py_compat_nodegroups :: HUnit.Assertion
319
case_py_compat_nodegroups = do
320
  let num_groups = 500::Int
321
  groups <- genSample (vectorOf num_groups genNodeGroup)
322
  let serialized = J.encode groups
323
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
324
  mapM_ (\group -> when (any (not . isAscii) (J.encode group)) .
325
                 HUnit.assertFailure $
326
                 "Node group has non-ASCII fields: " ++ show group
327
        ) groups
328
  py_stdout <-
329
    runPython "from ganeti import objects\n\
330
              \from ganeti import serializer\n\
331
              \import sys\n\
332
              \group_data = serializer.Load(sys.stdin.read())\n\
333
              \decoded = [objects.NodeGroup.FromDict(g) for g in group_data]\n\
334
              \encoded = [g.ToDict() for g in decoded]\n\
335
              \print serializer.Dump(encoded)" serialized
336
    >>= checkPythonResult
337
  let deserialised = J.decode py_stdout::J.Result [NodeGroup]
338
  decoded <- case deserialised of
339
               J.Ok ops -> return ops
340
               J.Error msg ->
341
                 HUnit.assertFailure ("Unable to decode node groups: " ++ msg)
342
                 -- this already raised an expection, but we need it
343
                 -- for proper types
344
                 >> fail "Unable to decode node groups"
345
  HUnit.assertEqual "Mismatch in number of returned node groups"
346
    (length decoded) (length groups)
347
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
348
        ) $ zip decoded groups
349

    
350
-- | Generates a node group with up to 3 networks.
351
-- | FIXME: This generates still somewhat completely random data, without normal
352
-- validation rules.
353
genNodeGroup :: Gen NodeGroup
354
genNodeGroup = do
355
  name <- genFQDN
356
  members <- pure []
357
  ndparams <- arbitrary
358
  alloc_policy <- arbitrary
359
  ipolicy <- arbitrary
360
  diskparams <- pure (GenericContainer Map.empty)
361
  num_networks <- choose (0, 3)
362
  net_uuid_list <- vectorOf num_networks (arbitrary::Gen String)
363
  nic_param_list <- vectorOf num_networks (arbitrary::Gen PartialNicParams)
364
  net_map <- pure (GenericContainer . Map.fromList $
365
    zip net_uuid_list nic_param_list)
366
  -- timestamp fields
367
  ctime <- arbitrary
368
  mtime <- arbitrary
369
  uuid <- arbitrary
370
  serial <- arbitrary
371
  tags <- Set.fromList <$> genTags
372
  let group = NodeGroup name members ndparams alloc_policy ipolicy diskparams
373
              net_map ctime mtime uuid serial tags
374
  return group
375

    
376
instance Arbitrary NodeGroup where
377
  arbitrary = genNodeGroup
378

    
379
testSuite "Objects"
380
  [ 'prop_fillDict
381
  , 'prop_Disk_serialisation
382
  , 'prop_Inst_serialisation
383
  , 'prop_Network_serialisation
384
  , 'prop_Node_serialisation
385
  , 'prop_Config_serialisation
386
  , 'case_py_compat_networks
387
  , 'case_py_compat_nodegroups
388
  ]