Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (19.5 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

    
66
-- * Arbitrary instances
67

    
68
$(genArbitrary ''PartialNDParams)
69

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

    
77
$(genArbitrary ''BlockDriver)
78

    
79
$(genArbitrary ''DiskMode)
80

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

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

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

    
102
$(genArbitrary ''AdminState)
103

    
104
$(genArbitrary ''PartialNicParams)
105

    
106
$(genArbitrary ''PartialNic)
107

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
230
$(genArbitrary ''Cluster)
231

    
232
instance Arbitrary Network where
233
  arbitrary = genValidNetwork
234

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

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

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

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

    
294
-- | FIXME: make an even simpler base version of creating a cluster.
295

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

    
312
-- * Test properties
313

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

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

    
338
-- | Check that node serialisation is idempotent.
339
prop_Node_serialisation :: Node -> Property
340
prop_Node_serialisation = testSerialisation
341

    
342
-- | Check that instance serialisation is idempotent.
343
prop_Inst_serialisation :: Instance -> Property
344
prop_Inst_serialisation = testSerialisation
345

    
346
-- | Check that network serialisation is idempotent.
347
prop_Network_serialisation :: Network -> Property
348
prop_Network_serialisation = testSerialisation
349

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

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

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

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

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

    
466
instance Arbitrary NodeGroup where
467
  arbitrary = genNodeGroup
468

    
469
$(genArbitrary ''Ip4Address)
470

    
471
$(genArbitrary ''Ip4Network)
472

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

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

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

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

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

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