Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 1d4a4b26

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
  let n = Network name mac_prefix (Ip4Network net netmask) net6 gateway
252
          gateway6 res ext_res uuid 0 Set.empty
253
  return n
254

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

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

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

    
292
-- | FIXME: make an even simpler base version of creating a cluster.
293

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

    
310
-- * Test properties
311

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

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

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

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

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

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

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

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

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

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

    
464
instance Arbitrary NodeGroup where
465
  arbitrary = genNodeGroup
466

    
467
$(genArbitrary ''Ip4Address)
468

    
469
$(genArbitrary ''Ip4Network)
470

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

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

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

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

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

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