Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (16.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
  , genEmptyCluster
35
  , genInstWithNets
36
  , genValidNetwork
37
  , genBitStringMaxLen
38
  ) where
39

    
40
import Test.QuickCheck
41
import qualified Test.HUnit as HUnit
42

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

    
53
import Test.Ganeti.TestHelper
54
import Test.Ganeti.TestCommon
55
import Test.Ganeti.Types ()
56

    
57
import qualified Ganeti.Constants as C
58
import Ganeti.Network
59
import Ganeti.Objects as Objects
60
import Ganeti.JSON
61
import Ganeti.Types
62

    
63
-- * Arbitrary instances
64

    
65
$(genArbitrary ''PartialNDParams)
66

    
67
instance Arbitrary Node where
68
  arbitrary = Node <$> genFQDN <*> genFQDN <*> genFQDN
69
              <*> arbitrary <*> arbitrary <*> arbitrary <*> genFQDN
70
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
71
              <*> arbitrary <*> arbitrary <*> genFQDN <*> arbitrary
72
              <*> (Set.fromList <$> genTags)
73

    
74
$(genArbitrary ''BlockDriver)
75

    
76
$(genArbitrary ''DiskMode)
77

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

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

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

    
98
$(genArbitrary ''AdminState)
99

    
100
$(genArbitrary ''PartialNicParams)
101

    
102
$(genArbitrary ''PartialNic)
103

    
104
instance Arbitrary Instance where
105
  arbitrary =
106
    Instance
107
      <$> genFQDN <*> genFQDN <*> genFQDN -- OS name, but...
108
      <*> arbitrary
109
      -- FIXME: add non-empty hvparams when they're a proper type
110
      <*> pure (GenericContainer Map.empty) <*> arbitrary
111
      -- ... and for OSParams
112
      <*> pure (GenericContainer Map.empty) <*> arbitrary <*> arbitrary
113
      <*> arbitrary <*> arbitrary <*> arbitrary
114
      -- ts
115
      <*> arbitrary <*> arbitrary
116
      -- uuid
117
      <*> arbitrary
118
      -- serial
119
      <*> arbitrary
120
      -- tags
121
      <*> (Set.fromList <$> genTags)
122

    
123
-- | Generates an instance that is connected to the given networks
124
-- and possibly some other networks
125
genInstWithNets :: [String] -> Gen Instance
126
genInstWithNets nets = do
127
  plain_inst <- arbitrary
128
  mac <- arbitrary
129
  ip <- arbitrary
130
  nicparams <- arbitrary
131
  -- generate some more networks than the given ones
132
  num_more_nets <- choose (0,3)
133
  more_nets <- vectorOf num_more_nets genName
134
  let partial_nics = map (PartialNic mac ip nicparams . Just)
135
                       (List.nub (nets ++ more_nets))
136
      new_inst = plain_inst { instNics = partial_nics }
137
  return new_inst
138

    
139
-- | FIXME: This generates completely random data, without normal
140
-- validation rules.
141
$(genArbitrary ''PartialISpecParams)
142

    
143
-- | FIXME: This generates completely random data, without normal
144
-- validation rules.
145
$(genArbitrary ''PartialIPolicy)
146

    
147
$(genArbitrary ''FilledISpecParams)
148
$(genArbitrary ''FilledIPolicy)
149
$(genArbitrary ''IpFamily)
150
$(genArbitrary ''FilledNDParams)
151
$(genArbitrary ''FilledNicParams)
152
$(genArbitrary ''FilledBeParams)
153

    
154
-- | No real arbitrary instance for 'ClusterHvParams' yet.
155
instance Arbitrary ClusterHvParams where
156
  arbitrary = return $ GenericContainer Map.empty
157

    
158
-- | No real arbitrary instance for 'OsHvParams' yet.
159
instance Arbitrary OsHvParams where
160
  arbitrary = return $ GenericContainer Map.empty
161

    
162
instance Arbitrary ClusterNicParams where
163
  arbitrary = (GenericContainer . Map.singleton C.ppDefault) <$> arbitrary
164

    
165
instance Arbitrary OsParams where
166
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
167

    
168
instance Arbitrary ClusterOsParams where
169
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
170

    
171
instance Arbitrary ClusterBeParams where
172
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
173

    
174
instance Arbitrary TagSet where
175
  arbitrary = Set.fromList <$> genTags
176

    
177
$(genArbitrary ''Cluster)
178

    
179
instance Arbitrary Network where
180
  arbitrary = genValidNetwork
181

    
182
-- | Generates a network instance with minimum netmasks of /24. Generating
183
-- bigger networks slows down the tests, because long bit strings are generated
184
-- for the reservations.
185
genValidNetwork :: Gen Objects.Network
186
genValidNetwork = do
187
  -- generate netmask for the IPv4 network
188
  netmask <- fromIntegral <$> choose (24::Int, 30)
189
  name <- genName >>= mkNonEmpty
190
  mac_prefix <- genMaybe genName
191
  net <- arbitrary
192
  net6 <- genMaybe genIp6Net
193
  gateway <- genMaybe arbitrary
194
  gateway6 <- genMaybe genIp6Addr
195
  res <- liftM Just (genBitString $ netmask2NumHosts netmask)
196
  ext_res <- liftM Just (genBitString $ netmask2NumHosts netmask)
197
  uuid <- arbitrary
198
  let n = Network name mac_prefix (Ip4Network net netmask) net6 gateway
199
          gateway6 res ext_res uuid 0 Set.empty
200
  return n
201

    
202
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
203
genBitString :: Int -> Gen String
204
genBitString len = vectorOf len (elements "01")
205

    
206
-- | Generate an arbitrary string consisting of '0' and '1' of the maximum given
207
-- length.
208
genBitStringMaxLen :: Int -> Gen String
209
genBitStringMaxLen maxLen = choose (0, maxLen) >>= genBitString
210

    
211
-- | Generator for config data with an empty cluster (no instances),
212
-- with N defined nodes.
213
genEmptyCluster :: Int -> Gen ConfigData
214
genEmptyCluster ncount = do
215
  nodes <- vector ncount
216
  version <- arbitrary
217
  grp <- arbitrary
218
  let guuid = groupUuid grp
219
      nodes' = zipWith (\n idx ->
220
                          let newname = nodeName n ++ "-" ++ show idx
221
                          in (newname, n { nodeGroup = guuid,
222
                                           nodeName = newname}))
223
               nodes [(1::Int)..]
224
      nodemap = Map.fromList nodes'
225
      contnodes = if Map.size nodemap /= ncount
226
                    then error ("Inconsistent node map, duplicates in" ++
227
                                " node name list? Names: " ++
228
                                show (map fst nodes'))
229
                    else GenericContainer nodemap
230
      continsts = GenericContainer Map.empty
231
      networks = GenericContainer Map.empty
232
  let contgroups = GenericContainer $ Map.singleton guuid grp
233
  serial <- arbitrary
234
  cluster <- resize 8 arbitrary
235
  let c = ConfigData version cluster contnodes contgroups continsts networks
236
            serial
237
  return c
238

    
239
-- | FIXME: make an even simpler base version of creating a cluster.
240

    
241
-- | Generates config data with a couple of networks.
242
genConfigDataWithNetworks :: ConfigData -> Gen ConfigData
243
genConfigDataWithNetworks old_cfg = do
244
  num_nets <- choose (0, 3)
245
  -- generate a list of network names (no duplicates)
246
  net_names <- genUniquesList num_nets genName >>= mapM mkNonEmpty
247
  -- generate a random list of networks (possibly with duplicate names)
248
  nets <- vectorOf num_nets genValidNetwork
249
  -- use unique names for the networks
250
  let nets_unique = map ( \(name, net) -> net { networkName = name } )
251
        (zip net_names nets)
252
      net_map = GenericContainer $ Map.fromList
253
        (map (\n -> (networkUuid n, n)) nets_unique)
254
      new_cfg = old_cfg { configNetworks = net_map }
255
  return new_cfg
256

    
257
-- * Test properties
258

    
259
-- | Tests that fillDict behaves correctly
260
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
261
prop_fillDict defaults custom =
262
  let d_map = Map.fromList defaults
263
      d_keys = map fst defaults
264
      c_map = Map.fromList custom
265
      c_keys = map fst custom
266
  in conjoin [ printTestCase "Empty custom filling"
267
               (fillDict d_map Map.empty [] == d_map)
268
             , printTestCase "Empty defaults filling"
269
               (fillDict Map.empty c_map [] == c_map)
270
             , printTestCase "Delete all keys"
271
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
272
             ]
273

    
274
-- | Test that the serialisation of 'DiskLogicalId', which is
275
-- implemented manually, is idempotent. Since we don't have a
276
-- standalone JSON instance for DiskLogicalId (it's a data type that
277
-- expands over two fields in a JSObject), we test this by actially
278
-- testing entire Disk serialisations. So this tests two things at
279
-- once, basically.
280
prop_Disk_serialisation :: Disk -> Property
281
prop_Disk_serialisation = testSerialisation
282

    
283
-- | Check that node serialisation is idempotent.
284
prop_Node_serialisation :: Node -> Property
285
prop_Node_serialisation = testSerialisation
286

    
287
-- | Check that instance serialisation is idempotent.
288
prop_Inst_serialisation :: Instance -> Property
289
prop_Inst_serialisation = testSerialisation
290

    
291
-- | Check that network serialisation is idempotent.
292
prop_Network_serialisation :: Network -> Property
293
prop_Network_serialisation = testSerialisation
294

    
295
-- | Check config serialisation.
296
prop_Config_serialisation :: Property
297
prop_Config_serialisation =
298
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
299

    
300
-- | Custom HUnit test to check the correspondence between Haskell-generated
301
-- networks and their Python decoded, validated and re-encoded version.
302
-- For the technical background of this unit test, check the documentation
303
-- of "case_py_compat_types" of test/hs/Test/Ganeti/Opcodes.hs
304
casePyCompatNetworks :: HUnit.Assertion
305
casePyCompatNetworks = do
306
  let num_networks = 500::Int
307
  networks <- genSample (vectorOf num_networks genValidNetwork)
308
  let networks_with_properties = map getNetworkProperties networks
309
      serialized = J.encode networks
310
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
311
  mapM_ (\net -> when (any (not . isAscii) (J.encode net)) .
312
                 HUnit.assertFailure $
313
                 "Network has non-ASCII fields: " ++ show net
314
        ) networks
315
  py_stdout <-
316
    runPython "from ganeti import network\n\
317
              \from ganeti import objects\n\
318
              \from ganeti import serializer\n\
319
              \import sys\n\
320
              \net_data = serializer.Load(sys.stdin.read())\n\
321
              \decoded = [objects.Network.FromDict(n) for n in net_data]\n\
322
              \encoded = []\n\
323
              \for net in decoded:\n\
324
              \  a = network.AddressPool(net)\n\
325
              \  encoded.append((a.GetFreeCount(), a.GetReservedCount(), \\\n\
326
              \    net.ToDict()))\n\
327
              \print serializer.Dump(encoded)" serialized
328
    >>= checkPythonResult
329
  let deserialised = J.decode py_stdout::J.Result [(Int, Int, Network)]
330
  decoded <- case deserialised of
331
               J.Ok ops -> return ops
332
               J.Error msg ->
333
                 HUnit.assertFailure ("Unable to decode networks: " ++ msg)
334
                 -- this already raised an expection, but we need it
335
                 -- for proper types
336
                 >> fail "Unable to decode networks"
337
  HUnit.assertEqual "Mismatch in number of returned networks"
338
    (length decoded) (length networks_with_properties)
339
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
340
        ) $ zip decoded networks_with_properties
341

    
342
-- | Creates a tuple of the given network combined with some of its properties
343
-- to be compared against the same properties generated by the python code.
344
getNetworkProperties :: Network -> (Int, Int, Network)
345
getNetworkProperties net =
346
  let maybePool = createAddressPool net
347
  in  case maybePool of
348
           (Just pool) -> (getFreeCount pool, getReservedCount pool, net)
349
           Nothing -> (-1, -1, net)
350

    
351
-- | Tests the compatibility between Haskell-serialized node groups and their
352
-- python-decoded and encoded version.
353
casePyCompatNodegroups :: HUnit.Assertion
354
casePyCompatNodegroups = do
355
  let num_groups = 500::Int
356
  groups <- genSample (vectorOf num_groups genNodeGroup)
357
  let serialized = J.encode groups
358
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
359
  mapM_ (\group -> when (any (not . isAscii) (J.encode group)) .
360
                 HUnit.assertFailure $
361
                 "Node group has non-ASCII fields: " ++ show group
362
        ) groups
363
  py_stdout <-
364
    runPython "from ganeti import objects\n\
365
              \from ganeti import serializer\n\
366
              \import sys\n\
367
              \group_data = serializer.Load(sys.stdin.read())\n\
368
              \decoded = [objects.NodeGroup.FromDict(g) for g in group_data]\n\
369
              \encoded = [g.ToDict() for g in decoded]\n\
370
              \print serializer.Dump(encoded)" serialized
371
    >>= checkPythonResult
372
  let deserialised = J.decode py_stdout::J.Result [NodeGroup]
373
  decoded <- case deserialised of
374
               J.Ok ops -> return ops
375
               J.Error msg ->
376
                 HUnit.assertFailure ("Unable to decode node groups: " ++ msg)
377
                 -- this already raised an expection, but we need it
378
                 -- for proper types
379
                 >> fail "Unable to decode node groups"
380
  HUnit.assertEqual "Mismatch in number of returned node groups"
381
    (length decoded) (length groups)
382
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
383
        ) $ zip decoded groups
384

    
385
-- | Generates a node group with up to 3 networks.
386
-- | FIXME: This generates still somewhat completely random data, without normal
387
-- validation rules.
388
genNodeGroup :: Gen NodeGroup
389
genNodeGroup = do
390
  name <- genFQDN
391
  members <- pure []
392
  ndparams <- arbitrary
393
  alloc_policy <- arbitrary
394
  ipolicy <- arbitrary
395
  diskparams <- pure (GenericContainer Map.empty)
396
  num_networks <- choose (0, 3)
397
  net_uuid_list <- vectorOf num_networks (arbitrary::Gen String)
398
  nic_param_list <- vectorOf num_networks (arbitrary::Gen PartialNicParams)
399
  net_map <- pure (GenericContainer . Map.fromList $
400
    zip net_uuid_list nic_param_list)
401
  -- timestamp fields
402
  ctime <- arbitrary
403
  mtime <- arbitrary
404
  uuid <- genFQDN `suchThat` (/= name)
405
  serial <- arbitrary
406
  tags <- Set.fromList <$> genTags
407
  let group = NodeGroup name members ndparams alloc_policy ipolicy diskparams
408
              net_map ctime mtime uuid serial tags
409
  return group
410

    
411
instance Arbitrary NodeGroup where
412
  arbitrary = genNodeGroup
413

    
414
$(genArbitrary ''Ip4Address)
415

    
416
$(genArbitrary ''Ip4Network)
417

    
418
-- | Helper to compute absolute value of an IPv4 address.
419
ip4AddrValue :: Ip4Address -> Integer
420
ip4AddrValue (Ip4Address a b c d) =
421
  fromIntegral a * (2^(24::Integer)) +
422
  fromIntegral b * (2^(16::Integer)) +
423
  fromIntegral c * (2^(8::Integer)) + fromIntegral d
424

    
425
-- | Tests that any difference between IPv4 consecutive addresses is 1.
426
prop_nextIp4Address :: Ip4Address -> Property
427
prop_nextIp4Address ip4 =
428
  ip4AddrValue (nextIp4Address ip4) ==? ip4AddrValue ip4 + 1
429

    
430
-- | IsString instance for 'Ip4Address', to help write the tests.
431
instance IsString Ip4Address where
432
  fromString s =
433
    fromMaybe (error $ "Failed to parse address from " ++ s) (readIp4Address s)
434

    
435
-- | Tests a few simple cases of IPv4 next address.
436
caseNextIp4Address :: HUnit.Assertion
437
caseNextIp4Address = do
438
  HUnit.assertEqual "" "0.0.0.1" $ nextIp4Address "0.0.0.0"
439
  HUnit.assertEqual "" "0.0.0.0" $ nextIp4Address "255.255.255.255"
440
  HUnit.assertEqual "" "1.2.3.5" $ nextIp4Address "1.2.3.4"
441
  HUnit.assertEqual "" "1.3.0.0" $ nextIp4Address "1.2.255.255"
442
  HUnit.assertEqual "" "1.2.255.63" $ nextIp4Address "1.2.255.62"
443

    
444
testSuite "Objects"
445
  [ 'prop_fillDict
446
  , 'prop_Disk_serialisation
447
  , 'prop_Inst_serialisation
448
  , 'prop_Network_serialisation
449
  , 'prop_Node_serialisation
450
  , 'prop_Config_serialisation
451
  , 'casePyCompatNetworks
452
  , 'casePyCompatNodegroups
453
  , 'prop_nextIp4Address
454
  , 'caseNextIp4Address
455
  ]