Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 11e90588

History | View | Annotate | Download (19.6 kB)

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

    
5
{-| Unittests for ganeti-htools.
6

    
7
-}
8

    
9
{-
10

    
11
Copyright (C) 2009, 2010, 2011, 2012, 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

    
30
module Test.Ganeti.Objects
31
  ( testObjects
32
  , Node(..)
33
  , genConfigDataWithNetworks
34
  , genDisk
35
  , genDiskWithChildren
36
  , genEmptyCluster
37
  , genInst
38
  , genInstWithNets
39
  , genValidNetwork
40
  , genBitStringMaxLen
41
  ) where
42

    
43
import Test.QuickCheck
44
import qualified Test.HUnit as HUnit
45

    
46
import Control.Applicative
47
import Control.Monad
48
import Data.Char
49
import qualified Data.List as List
50
import qualified Data.Map as Map
51
import Data.Maybe (fromMaybe)
52
import qualified Data.Set as Set
53
import GHC.Exts (IsString(..))
54
import qualified Text.JSON as J
55

    
56
import Test.Ganeti.TestHelper
57
import Test.Ganeti.TestCommon
58
import Test.Ganeti.Types ()
59

    
60
import qualified Ganeti.Constants as C
61
import Ganeti.Network
62
import Ganeti.Objects as Objects
63
import Ganeti.JSON
64
import Ganeti.Types
65
import Ganeti.Utils (bitStringToB64String)
66

    
67
-- * Arbitrary instances
68

    
69
$(genArbitrary ''PartialNDParams)
70

    
71
instance Arbitrary Node where
72
  arbitrary = Node <$> genFQDN <*> genFQDN <*> genFQDN
73
              <*> arbitrary <*> arbitrary <*> arbitrary <*> genFQDN
74
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
75
              <*> arbitrary <*> arbitrary <*> genFQDN <*> arbitrary
76
              <*> (Set.fromList <$> genTags)
77

    
78
$(genArbitrary ''BlockDriver)
79

    
80
$(genArbitrary ''DiskMode)
81

    
82
instance Arbitrary DiskLogicalId where
83
  arbitrary = oneof [ LIDPlain <$> arbitrary <*> arbitrary
84
                    , LIDDrbd8 <$> genFQDN <*> genFQDN <*> arbitrary
85
                               <*> arbitrary <*> arbitrary <*> arbitrary
86
                    , LIDFile  <$> arbitrary <*> arbitrary
87
                    , LIDBlockDev <$> arbitrary <*> arbitrary
88
                    , LIDRados <$> arbitrary <*> arbitrary
89
                    ]
90

    
91
-- | 'Disk' 'arbitrary' instance. Since we don't test disk hierarchy
92
-- properties, we only generate disks with no children (FIXME), as
93
-- generating recursive datastructures is a bit more work.
94
instance Arbitrary Disk where
95
  arbitrary = Disk <$> arbitrary <*> pure [] <*> arbitrary
96
                   <*> arbitrary <*> arbitrary <*> arbitrary
97
                   <*> arbitrary
98

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

    
103
$(genArbitrary ''AdminState)
104

    
105
$(genArbitrary ''PartialNicParams)
106

    
107
$(genArbitrary ''PartialNic)
108

    
109
instance Arbitrary Instance where
110
  arbitrary =
111
    Instance
112
      -- name
113
      <$> genFQDN
114
      -- primary node
115
      <*> genFQDN
116
      -- OS
117
      <*> genFQDN
118
      -- hypervisor
119
      <*> arbitrary
120
      -- hvparams
121
      -- FIXME: add non-empty hvparams when they're a proper type
122
      <*> pure (GenericContainer Map.empty)
123
      -- beparams
124
      <*> arbitrary
125
      -- osparams
126
      <*> pure (GenericContainer Map.empty)
127
      -- admin_state
128
      <*> arbitrary
129
      -- nics
130
      <*> arbitrary
131
      -- disks
132
      <*> vectorOf 5 genDisk
133
      -- disk template
134
      <*> arbitrary
135
      -- disks active
136
      <*> arbitrary
137
      -- network port
138
      <*> arbitrary
139
      -- ts
140
      <*> arbitrary <*> arbitrary
141
      -- uuid
142
      <*> arbitrary
143
      -- serial
144
      <*> arbitrary
145
      -- tags
146
      <*> (Set.fromList <$> genTags)
147

    
148
-- | Generates an instance that is connected to the given networks
149
-- and possibly some other networks
150
genInstWithNets :: [String] -> Gen Instance
151
genInstWithNets nets = do
152
  plain_inst <- arbitrary
153
  enhanceInstWithNets plain_inst nets
154

    
155
-- | Generates an instance that is connected to some networks
156
genInst :: Gen Instance
157
genInst = genInstWithNets []
158

    
159
-- | Enhances a given instance with network information, by connecting it to the
160
-- given networks and possibly some other networks
161
enhanceInstWithNets :: Instance -> [String] -> Gen Instance
162
enhanceInstWithNets inst nets = do
163
  mac <- arbitrary
164
  ip <- arbitrary
165
  nicparams <- arbitrary
166
  name <- arbitrary
167
  uuid <- arbitrary
168
  -- generate some more networks than the given ones
169
  num_more_nets <- choose (0,3)
170
  more_nets <- vectorOf num_more_nets genName
171
  let genNic net = PartialNic mac ip nicparams net name uuid
172
      partial_nics = map (genNic . Just)
173
                         (List.nub (nets ++ more_nets))
174
      new_inst = inst { instNics = partial_nics }
175
  return new_inst
176

    
177
genDiskWithChildren :: Int -> Gen Disk
178
genDiskWithChildren num_children = do
179
  logicalid <- arbitrary
180
  children <- vectorOf num_children (genDiskWithChildren 0)
181
  ivname <- genName
182
  size <- arbitrary
183
  mode <- arbitrary
184
  name <- genMaybe genName
185
  uuid <- genName
186
  let disk = Disk logicalid children ivname size mode name uuid
187
  return disk
188

    
189
genDisk :: Gen Disk
190
genDisk = genDiskWithChildren 3
191

    
192
-- | FIXME: This generates completely random data, without normal
193
-- validation rules.
194
$(genArbitrary ''PartialISpecParams)
195

    
196
-- | FIXME: This generates completely random data, without normal
197
-- validation rules.
198
$(genArbitrary ''PartialIPolicy)
199

    
200
$(genArbitrary ''FilledISpecParams)
201
$(genArbitrary ''MinMaxISpecs)
202
$(genArbitrary ''FilledIPolicy)
203
$(genArbitrary ''IpFamily)
204
$(genArbitrary ''FilledNDParams)
205
$(genArbitrary ''FilledNicParams)
206
$(genArbitrary ''FilledBeParams)
207

    
208
-- | No real arbitrary instance for 'ClusterHvParams' yet.
209
instance Arbitrary ClusterHvParams where
210
  arbitrary = return $ GenericContainer Map.empty
211

    
212
-- | No real arbitrary instance for 'OsHvParams' yet.
213
instance Arbitrary OsHvParams where
214
  arbitrary = return $ GenericContainer Map.empty
215

    
216
instance Arbitrary ClusterNicParams where
217
  arbitrary = (GenericContainer . Map.singleton C.ppDefault) <$> arbitrary
218

    
219
instance Arbitrary OsParams where
220
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
221

    
222
instance Arbitrary ClusterOsParams where
223
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
224

    
225
instance Arbitrary ClusterBeParams where
226
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
227

    
228
instance Arbitrary TagSet where
229
  arbitrary = Set.fromList <$> genTags
230

    
231
$(genArbitrary ''Cluster)
232

    
233
instance Arbitrary Network where
234
  arbitrary = genValidNetwork
235

    
236
-- | Generates a network instance with minimum netmasks of /24. Generating
237
-- bigger networks slows down the tests, because long bit strings are generated
238
-- for the reservations.
239
genValidNetwork :: Gen Objects.Network
240
genValidNetwork = do
241
  -- generate netmask for the IPv4 network
242
  netmask <- fromIntegral <$> choose (24::Int, 29)
243
  name <- genName >>= mkNonEmpty
244
  mac_prefix <- genMaybe genName
245
  net <- arbitrary
246
  net6 <- genMaybe genIp6Net
247
  gateway <- genMaybe arbitrary
248
  gateway6 <- genMaybe genIp6Addr
249
  res <- liftM (Just . bitStringToB64String)
250
         (genBitString $ netmask2NumHosts netmask)
251
  ext_res <- liftM (Just . bitStringToB64String)
252
             (genBitString $ netmask2NumHosts netmask)
253
  uuid <- arbitrary
254
  ctime <- arbitrary
255
  mtime <- arbitrary
256
  let n = Network name mac_prefix (Ip4Network net netmask) net6 gateway
257
          gateway6 res ext_res uuid ctime mtime 0 Set.empty
258
  return n
259

    
260
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
261
genBitString :: Int -> Gen String
262
genBitString len = vectorOf len (elements "01")
263

    
264
-- | Generate an arbitrary string consisting of '0' and '1' of the maximum given
265
-- length.
266
genBitStringMaxLen :: Int -> Gen String
267
genBitStringMaxLen maxLen = choose (0, maxLen) >>= genBitString
268

    
269
-- | Generator for config data with an empty cluster (no instances),
270
-- with N defined nodes.
271
genEmptyCluster :: Int -> Gen ConfigData
272
genEmptyCluster ncount = do
273
  nodes <- vector ncount
274
  version <- arbitrary
275
  grp <- arbitrary
276
  let guuid = groupUuid grp
277
      nodes' = zipWith (\n idx ->
278
                          let newname = nodeName n ++ "-" ++ show idx
279
                          in (newname, n { nodeGroup = guuid,
280
                                           nodeName = newname}))
281
               nodes [(1::Int)..]
282
      nodemap = Map.fromList nodes'
283
      contnodes = if Map.size nodemap /= ncount
284
                    then error ("Inconsistent node map, duplicates in" ++
285
                                " node name list? Names: " ++
286
                                show (map fst nodes'))
287
                    else GenericContainer nodemap
288
      continsts = GenericContainer Map.empty
289
      networks = GenericContainer Map.empty
290
  let contgroups = GenericContainer $ Map.singleton guuid grp
291
  serial <- arbitrary
292
  cluster <- resize 8 arbitrary
293
  let c = ConfigData version cluster contnodes contgroups continsts networks
294
            serial
295
  return c
296

    
297
-- | FIXME: make an even simpler base version of creating a cluster.
298

    
299
-- | Generates config data with a couple of networks.
300
genConfigDataWithNetworks :: ConfigData -> Gen ConfigData
301
genConfigDataWithNetworks old_cfg = do
302
  num_nets <- choose (0, 3)
303
  -- generate a list of network names (no duplicates)
304
  net_names <- genUniquesList num_nets genName >>= mapM mkNonEmpty
305
  -- generate a random list of networks (possibly with duplicate names)
306
  nets <- vectorOf num_nets genValidNetwork
307
  -- use unique names for the networks
308
  let nets_unique = map ( \(name, net) -> net { networkName = name } )
309
        (zip net_names nets)
310
      net_map = GenericContainer $ Map.fromList
311
        (map (\n -> (networkUuid n, n)) nets_unique)
312
      new_cfg = old_cfg { configNetworks = net_map }
313
  return new_cfg
314

    
315
-- * Test properties
316

    
317
-- | Tests that fillDict behaves correctly
318
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
319
prop_fillDict defaults custom =
320
  let d_map = Map.fromList defaults
321
      d_keys = map fst defaults
322
      c_map = Map.fromList custom
323
      c_keys = map fst custom
324
  in conjoin [ printTestCase "Empty custom filling"
325
               (fillDict d_map Map.empty [] == d_map)
326
             , printTestCase "Empty defaults filling"
327
               (fillDict Map.empty c_map [] == c_map)
328
             , printTestCase "Delete all keys"
329
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
330
             ]
331

    
332
-- | Test that the serialisation of 'DiskLogicalId', which is
333
-- implemented manually, is idempotent. Since we don't have a
334
-- standalone JSON instance for DiskLogicalId (it's a data type that
335
-- expands over two fields in a JSObject), we test this by actially
336
-- testing entire Disk serialisations. So this tests two things at
337
-- once, basically.
338
prop_Disk_serialisation :: Disk -> Property
339
prop_Disk_serialisation = testSerialisation
340

    
341
-- | Check that node serialisation is idempotent.
342
prop_Node_serialisation :: Node -> Property
343
prop_Node_serialisation = testSerialisation
344

    
345
-- | Check that instance serialisation is idempotent.
346
prop_Inst_serialisation :: Instance -> Property
347
prop_Inst_serialisation = testSerialisation
348

    
349
-- | Check that network serialisation is idempotent.
350
prop_Network_serialisation :: Network -> Property
351
prop_Network_serialisation = testSerialisation
352

    
353
-- | Check config serialisation.
354
prop_Config_serialisation :: Property
355
prop_Config_serialisation =
356
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
357

    
358
-- | Custom HUnit test to check the correspondence between Haskell-generated
359
-- networks and their Python decoded, validated and re-encoded version.
360
-- For the technical background of this unit test, check the documentation
361
-- of "case_py_compat_types" of test/hs/Test/Ganeti/Opcodes.hs
362
casePyCompatNetworks :: HUnit.Assertion
363
casePyCompatNetworks = do
364
  let num_networks = 500::Int
365
  networks <- genSample (vectorOf num_networks genValidNetwork)
366
  let networks_with_properties = map getNetworkProperties networks
367
      serialized = J.encode networks
368
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
369
  mapM_ (\net -> when (any (not . isAscii) (J.encode net)) .
370
                 HUnit.assertFailure $
371
                 "Network has non-ASCII fields: " ++ show net
372
        ) networks
373
  py_stdout <-
374
    runPython "from ganeti import network\n\
375
              \from ganeti import objects\n\
376
              \from ganeti import serializer\n\
377
              \import sys\n\
378
              \net_data = serializer.Load(sys.stdin.read())\n\
379
              \decoded = [objects.Network.FromDict(n) for n in net_data]\n\
380
              \encoded = []\n\
381
              \for net in decoded:\n\
382
              \  a = network.AddressPool(net)\n\
383
              \  encoded.append((a.GetFreeCount(), a.GetReservedCount(), \\\n\
384
              \    net.ToDict()))\n\
385
              \print serializer.Dump(encoded)" serialized
386
    >>= checkPythonResult
387
  let deserialised = J.decode py_stdout::J.Result [(Int, Int, Network)]
388
  decoded <- case deserialised of
389
               J.Ok ops -> return ops
390
               J.Error msg ->
391
                 HUnit.assertFailure ("Unable to decode networks: " ++ msg)
392
                 -- this already raised an expection, but we need it
393
                 -- for proper types
394
                 >> fail "Unable to decode networks"
395
  HUnit.assertEqual "Mismatch in number of returned networks"
396
    (length decoded) (length networks_with_properties)
397
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
398
        ) $ zip decoded networks_with_properties
399

    
400
-- | Creates a tuple of the given network combined with some of its properties
401
-- to be compared against the same properties generated by the python code.
402
getNetworkProperties :: Network -> (Int, Int, Network)
403
getNetworkProperties net =
404
  let maybePool = createAddressPool net
405
  in  case maybePool of
406
           (Just pool) -> (getFreeCount pool, getReservedCount pool, net)
407
           Nothing -> (-1, -1, net)
408

    
409
-- | Tests the compatibility between Haskell-serialized node groups and their
410
-- python-decoded and encoded version.
411
casePyCompatNodegroups :: HUnit.Assertion
412
casePyCompatNodegroups = do
413
  let num_groups = 500::Int
414
  groups <- genSample (vectorOf num_groups genNodeGroup)
415
  let serialized = J.encode groups
416
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
417
  mapM_ (\group -> when (any (not . isAscii) (J.encode group)) .
418
                 HUnit.assertFailure $
419
                 "Node group has non-ASCII fields: " ++ show group
420
        ) groups
421
  py_stdout <-
422
    runPython "from ganeti import objects\n\
423
              \from ganeti import serializer\n\
424
              \import sys\n\
425
              \group_data = serializer.Load(sys.stdin.read())\n\
426
              \decoded = [objects.NodeGroup.FromDict(g) for g in group_data]\n\
427
              \encoded = [g.ToDict() for g in decoded]\n\
428
              \print serializer.Dump(encoded)" serialized
429
    >>= checkPythonResult
430
  let deserialised = J.decode py_stdout::J.Result [NodeGroup]
431
  decoded <- case deserialised of
432
               J.Ok ops -> return ops
433
               J.Error msg ->
434
                 HUnit.assertFailure ("Unable to decode node groups: " ++ msg)
435
                 -- this already raised an expection, but we need it
436
                 -- for proper types
437
                 >> fail "Unable to decode node groups"
438
  HUnit.assertEqual "Mismatch in number of returned node groups"
439
    (length decoded) (length groups)
440
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
441
        ) $ zip decoded groups
442

    
443
-- | Generates a node group with up to 3 networks.
444
-- | FIXME: This generates still somewhat completely random data, without normal
445
-- validation rules.
446
genNodeGroup :: Gen NodeGroup
447
genNodeGroup = do
448
  name <- genFQDN
449
  members <- pure []
450
  ndparams <- arbitrary
451
  alloc_policy <- arbitrary
452
  ipolicy <- arbitrary
453
  diskparams <- pure (GenericContainer Map.empty)
454
  num_networks <- choose (0, 3)
455
  net_uuid_list <- vectorOf num_networks (arbitrary::Gen String)
456
  nic_param_list <- vectorOf num_networks (arbitrary::Gen PartialNicParams)
457
  net_map <- pure (GenericContainer . Map.fromList $
458
    zip net_uuid_list nic_param_list)
459
  -- timestamp fields
460
  ctime <- arbitrary
461
  mtime <- arbitrary
462
  uuid <- genFQDN `suchThat` (/= name)
463
  serial <- arbitrary
464
  tags <- Set.fromList <$> genTags
465
  let group = NodeGroup name members ndparams alloc_policy ipolicy diskparams
466
              net_map ctime mtime uuid serial tags
467
  return group
468

    
469
instance Arbitrary NodeGroup where
470
  arbitrary = genNodeGroup
471

    
472
$(genArbitrary ''Ip4Address)
473

    
474
$(genArbitrary ''Ip4Network)
475

    
476
-- | Helper to compute absolute value of an IPv4 address.
477
ip4AddrValue :: Ip4Address -> Integer
478
ip4AddrValue (Ip4Address a b c d) =
479
  fromIntegral a * (2^(24::Integer)) +
480
  fromIntegral b * (2^(16::Integer)) +
481
  fromIntegral c * (2^(8::Integer)) + fromIntegral d
482

    
483
-- | Tests that any difference between IPv4 consecutive addresses is 1.
484
prop_nextIp4Address :: Ip4Address -> Property
485
prop_nextIp4Address ip4 =
486
  ip4AddrValue (nextIp4Address ip4) ==? ip4AddrValue ip4 + 1
487

    
488
-- | IsString instance for 'Ip4Address', to help write the tests.
489
instance IsString Ip4Address where
490
  fromString s =
491
    fromMaybe (error $ "Failed to parse address from " ++ s) (readIp4Address s)
492

    
493
-- | Tests a few simple cases of IPv4 next address.
494
caseNextIp4Address :: HUnit.Assertion
495
caseNextIp4Address = do
496
  HUnit.assertEqual "" "0.0.0.1" $ nextIp4Address "0.0.0.0"
497
  HUnit.assertEqual "" "0.0.0.0" $ nextIp4Address "255.255.255.255"
498
  HUnit.assertEqual "" "1.2.3.5" $ nextIp4Address "1.2.3.4"
499
  HUnit.assertEqual "" "1.3.0.0" $ nextIp4Address "1.2.255.255"
500
  HUnit.assertEqual "" "1.2.255.63" $ nextIp4Address "1.2.255.62"
501

    
502
-- | Tests the compatibility between Haskell-serialized instances and their
503
-- python-decoded and encoded version.
504
-- Note: this can be enhanced with logical validations on the decoded objects
505
casePyCompatInstances :: HUnit.Assertion
506
casePyCompatInstances = do
507
  let num_inst = 500::Int
508
  instances <- genSample (vectorOf num_inst genInst)
509
  let serialized = J.encode instances
510
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
511
  mapM_ (\inst -> when (any (not . isAscii) (J.encode inst)) .
512
                 HUnit.assertFailure $
513
                 "Instance has non-ASCII fields: " ++ show inst
514
        ) instances
515
  py_stdout <-
516
    runPython "from ganeti import objects\n\
517
              \from ganeti import serializer\n\
518
              \import sys\n\
519
              \inst_data = serializer.Load(sys.stdin.read())\n\
520
              \decoded = [objects.Instance.FromDict(i) for i in inst_data]\n\
521
              \encoded = [i.ToDict() for i in decoded]\n\
522
              \print serializer.Dump(encoded)" serialized
523
    >>= checkPythonResult
524
  let deserialised = J.decode py_stdout::J.Result [Instance]
525
  decoded <- case deserialised of
526
               J.Ok ops -> return ops
527
               J.Error msg ->
528
                 HUnit.assertFailure ("Unable to decode instance: " ++ msg)
529
                 -- this already raised an expection, but we need it
530
                 -- for proper types
531
                 >> fail "Unable to decode instances"
532
  HUnit.assertEqual "Mismatch in number of returned instances"
533
    (length decoded) (length instances)
534
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
535
        ) $ zip decoded instances
536

    
537
testSuite "Objects"
538
  [ 'prop_fillDict
539
  , 'prop_Disk_serialisation
540
  , 'prop_Inst_serialisation
541
  , 'prop_Network_serialisation
542
  , 'prop_Node_serialisation
543
  , 'prop_Config_serialisation
544
  , 'casePyCompatNetworks
545
  , 'casePyCompatNodegroups
546
  , 'casePyCompatInstances
547
  , 'prop_nextIp4Address
548
  , 'caseNextIp4Address
549
  ]