Statistics
| Branch: | Tag: | Revision:

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

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 <*> 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
      -- network port
135
      <*> arbitrary
136
      -- ts
137
      <*> arbitrary <*> arbitrary
138
      -- uuid
139
      <*> arbitrary
140
      -- serial
141
      <*> arbitrary
142
      -- tags
143
      <*> (Set.fromList <$> genTags)
144

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
229
$(genArbitrary ''Cluster)
230

    
231
instance Arbitrary Network where
232
  arbitrary = genValidNetwork
233

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

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

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

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

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

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

    
309
-- * Test properties
310

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

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

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

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

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

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

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

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

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

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

    
463
instance Arbitrary NodeGroup where
464
  arbitrary = genNodeGroup
465

    
466
$(genArbitrary ''Ip4Address)
467

    
468
$(genArbitrary ''Ip4Network)
469

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

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

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

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

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

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