Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 596470db

History | View | Annotate | Download (19.7 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
  uuid <- arbitrary
246
  res <- liftM Just (genBitString $ netmask2NumHosts netmask)
247
  ext_res <- liftM Just (genZeroedBitString $ netmask2NumHosts netmask)
248
  let n = Network name mac_prefix (Just $ Ip4Network net netmask) net6 Nothing
249
          Nothing res ext_res uuid 0 Set.empty
250
  return n
251

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

    
256
genZeroedBitString :: Int -> Gen String
257
genZeroedBitString len = vectorOf len (elements "0")
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.Network(net)\n\
378
              \  if net.network:\n\
379
              \    encoded.append((a._GetFreeCount(), \\\n\
380
              \                   a._GetReservedCount(), \\\n\
381
              \                   net.ToDict()))\n\
382
              \  else:\n\
383
              \    encoded.append((-1, -1, \\\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
  ]