Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ de36f091

History | View | Annotate | Download (25.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Test.Ganeti.OpCodes
30
  ( testOpCodes
31
  , OpCodes.OpCode(..)
32
  ) where
33

    
34
import Test.HUnit as HUnit
35
import Test.QuickCheck as QuickCheck
36

    
37
import Control.Applicative
38
import Control.Monad
39
import Data.Char
40
import Data.List
41
import qualified Data.Map as Map
42
import qualified Text.JSON as J
43
import Text.Printf (printf)
44

    
45
import Test.Ganeti.TestHelper
46
import Test.Ganeti.TestCommon
47
import Test.Ganeti.Types ()
48
import Test.Ganeti.Query.Language ()
49

    
50
import Ganeti.BasicTypes
51
import qualified Ganeti.Constants as C
52
import qualified Ganeti.OpCodes as OpCodes
53
import Ganeti.Types
54
import Ganeti.OpParams
55
import Ganeti.JSON
56

    
57
{-# ANN module "HLint: ignore Use camelCase" #-}
58

    
59
-- * Arbitrary instances
60

    
61
instance (Ord k, Arbitrary k, Arbitrary a) => Arbitrary (Map.Map k a) where
62
  arbitrary = Map.fromList <$> arbitrary
63

    
64
arbitraryOpTagsGet :: Gen OpCodes.OpCode
65
arbitraryOpTagsGet = do
66
  kind <- arbitrary
67
  OpCodes.OpTagsSet kind <$> arbitrary <*> genOpCodesTagName kind
68

    
69
arbitraryOpTagsSet :: Gen OpCodes.OpCode
70
arbitraryOpTagsSet = do
71
  kind <- arbitrary
72
  OpCodes.OpTagsSet kind <$> genTags <*> genOpCodesTagName kind
73

    
74
arbitraryOpTagsDel :: Gen OpCodes.OpCode
75
arbitraryOpTagsDel = do
76
  kind <- arbitrary
77
  OpCodes.OpTagsDel kind <$> genTags <*> genOpCodesTagName kind
78

    
79
$(genArbitrary ''OpCodes.ReplaceDisksMode)
80

    
81
$(genArbitrary ''DiskAccess)
82

    
83
instance Arbitrary OpCodes.DiskIndex where
84
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
85

    
86
instance Arbitrary INicParams where
87
  arbitrary = INicParams <$> genMaybe genNameNE <*> genMaybe genName <*>
88
              genMaybe genNameNE <*> genMaybe genNameNE <*>
89
              genMaybe genNameNE <*> genMaybe genNameNE <*>
90
              genMaybe genNameNE
91

    
92
instance Arbitrary IDiskParams where
93
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
94
              genMaybe genNameNE <*> genMaybe genNameNE <*>
95
              genMaybe genNameNE <*> genMaybe genNameNE
96

    
97
instance Arbitrary RecreateDisksInfo where
98
  arbitrary = oneof [ pure RecreateDisksAll
99
                    , RecreateDisksIndices <$> arbitrary
100
                    , RecreateDisksParams <$> arbitrary
101
                    ]
102

    
103
instance Arbitrary DdmOldChanges where
104
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
105
                    , DdmOldMod   <$> arbitrary
106
                    ]
107

    
108
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
109
  arbitrary = oneof [ pure SetParamsEmpty
110
                    , SetParamsDeprecated <$> arbitrary
111
                    , SetParamsNew        <$> arbitrary
112
                    ]
113

    
114
instance Arbitrary ExportTarget where
115
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
116
                    , ExportTargetRemote <$> pure []
117
                    ]
118

    
119
instance Arbitrary OpCodes.OpCode where
120
  arbitrary = do
121
    op_id <- elements OpCodes.allOpIDs
122
    case op_id of
123
      "OP_TEST_DELAY" ->
124
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary <*>
125
          genNodeNamesNE <*> return Nothing <*> arbitrary
126
      "OP_INSTANCE_REPLACE_DISKS" ->
127
        OpCodes.OpInstanceReplaceDisks <$> genFQDN <*> return Nothing <*>
128
          arbitrary <*> arbitrary <*> arbitrary <*> genDiskIndices <*>
129
          genMaybe genNodeNameNE <*> return Nothing <*> genMaybe genNameNE
130
      "OP_INSTANCE_FAILOVER" ->
131
        OpCodes.OpInstanceFailover <$> genFQDN <*> return Nothing <*>
132
        arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
133
        return Nothing <*> arbitrary <*> genMaybe genNameNE
134
      "OP_INSTANCE_MIGRATE" ->
135
        OpCodes.OpInstanceMigrate <$> genFQDN <*> return Nothing <*>
136
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
137
          return Nothing <*> arbitrary <*> arbitrary <*> arbitrary <*>
138
          genMaybe genNameNE <*> arbitrary
139
      "OP_TAGS_GET" ->
140
        arbitraryOpTagsGet
141
      "OP_TAGS_SEARCH" ->
142
        OpCodes.OpTagsSearch <$> genNameNE
143
      "OP_TAGS_SET" ->
144
        arbitraryOpTagsSet
145
      "OP_TAGS_DEL" ->
146
        arbitraryOpTagsDel
147
      "OP_CLUSTER_POST_INIT" -> pure OpCodes.OpClusterPostInit
148
      "OP_CLUSTER_DESTROY" -> pure OpCodes.OpClusterDestroy
149
      "OP_CLUSTER_QUERY" -> pure OpCodes.OpClusterQuery
150
      "OP_CLUSTER_VERIFY" ->
151
        OpCodes.OpClusterVerify <$> arbitrary <*> arbitrary <*>
152
          genSet Nothing <*> genSet Nothing <*> arbitrary <*>
153
          genMaybe genNameNE
154
      "OP_CLUSTER_VERIFY_CONFIG" ->
155
        OpCodes.OpClusterVerifyConfig <$> arbitrary <*> arbitrary <*>
156
          genSet Nothing <*> arbitrary
157
      "OP_CLUSTER_VERIFY_GROUP" ->
158
        OpCodes.OpClusterVerifyGroup <$> genNameNE <*> arbitrary <*>
159
          arbitrary <*> genSet Nothing <*> genSet Nothing <*> arbitrary
160
      "OP_CLUSTER_VERIFY_DISKS" -> pure OpCodes.OpClusterVerifyDisks
161
      "OP_GROUP_VERIFY_DISKS" ->
162
        OpCodes.OpGroupVerifyDisks <$> genNameNE
163
      "OP_CLUSTER_REPAIR_DISK_SIZES" ->
164
        OpCodes.OpClusterRepairDiskSizes <$> genNodeNamesNE
165
      "OP_CLUSTER_CONFIG_QUERY" ->
166
        OpCodes.OpClusterConfigQuery <$> genFieldsNE
167
      "OP_CLUSTER_RENAME" ->
168
        OpCodes.OpClusterRename <$> genNameNE
169
      "OP_CLUSTER_SET_PARAMS" ->
170
        OpCodes.OpClusterSetParams <$> arbitrary <*> emptyMUD <*> emptyMUD <*>
171
          arbitrary <*> genMaybe arbitrary <*>
172
          genMaybe genEmptyContainer <*> emptyMUD <*>
173
          genMaybe genEmptyContainer <*> genMaybe genEmptyContainer <*>
174
          genMaybe genEmptyContainer <*> genMaybe arbitrary <*>
175
          arbitrary <*> arbitrary <*> arbitrary <*>
176
          arbitrary <*> arbitrary <*> arbitrary <*>
177
          emptyMUD <*> emptyMUD <*> arbitrary <*>
178
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
179
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
180
          genMaybe (genName >>= mkNonEmpty)
181
      "OP_CLUSTER_REDIST_CONF" -> pure OpCodes.OpClusterRedistConf
182
      "OP_CLUSTER_ACTIVATE_MASTER_IP" ->
183
        pure OpCodes.OpClusterActivateMasterIp
184
      "OP_CLUSTER_DEACTIVATE_MASTER_IP" ->
185
        pure OpCodes.OpClusterDeactivateMasterIp
186
      "OP_QUERY" ->
187
        OpCodes.OpQuery <$> arbitrary <*> arbitrary <*> arbitrary <*>
188
        pure Nothing
189
      "OP_QUERY_FIELDS" ->
190
        OpCodes.OpQueryFields <$> arbitrary <*> arbitrary
191
      "OP_OOB_COMMAND" ->
192
        OpCodes.OpOobCommand <$> genNodeNamesNE <*> return Nothing <*>
193
          arbitrary <*> arbitrary <*> arbitrary <*>
194
          (arbitrary `suchThat` (>0))
195
      "OP_NODE_REMOVE" ->
196
        OpCodes.OpNodeRemove <$> genNodeNameNE <*> return Nothing
197
      "OP_NODE_ADD" ->
198
        OpCodes.OpNodeAdd <$> genNodeNameNE <*> emptyMUD <*> emptyMUD <*>
199
          genNameNE <*> genMaybe genNameNE <*> arbitrary <*>
200
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> emptyMUD
201
      "OP_NODE_QUERY" ->
202
        OpCodes.OpNodeQuery <$> genFieldsNE <*> genNamesNE <*> arbitrary
203
      "OP_NODE_QUERYVOLS" ->
204
        OpCodes.OpNodeQueryvols <$> arbitrary <*> genNodeNamesNE
205
      "OP_NODE_QUERY_STORAGE" ->
206
        OpCodes.OpNodeQueryStorage <$> arbitrary <*> arbitrary <*>
207
          genNodeNamesNE <*> genMaybe genNameNE
208
      "OP_NODE_MODIFY_STORAGE" ->
209
        OpCodes.OpNodeModifyStorage <$> genNodeNameNE <*> return Nothing <*>
210
          arbitrary <*> genMaybe genNameNE <*> pure emptyJSObject
211
      "OP_REPAIR_NODE_STORAGE" ->
212
        OpCodes.OpRepairNodeStorage <$> genNodeNameNE <*> return Nothing <*>
213
          arbitrary <*> genMaybe genNameNE <*> arbitrary
214
      "OP_NODE_SET_PARAMS" ->
215
        OpCodes.OpNodeSetParams <$> genNodeNameNE <*> return Nothing <*>
216
          arbitrary <*> emptyMUD <*> emptyMUD <*> arbitrary <*> arbitrary <*>
217
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
218
          genMaybe genNameNE <*> emptyMUD <*> arbitrary
219
      "OP_NODE_POWERCYCLE" ->
220
        OpCodes.OpNodePowercycle <$> genNodeNameNE <*> return Nothing <*>
221
          arbitrary
222
      "OP_NODE_MIGRATE" ->
223
        OpCodes.OpNodeMigrate <$> genNodeNameNE <*> return Nothing <*>
224
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
225
          return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
226
      "OP_NODE_EVACUATE" ->
227
        OpCodes.OpNodeEvacuate <$> arbitrary <*> genNodeNameNE <*>
228
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
229
          genMaybe genNameNE <*> arbitrary
230
      "OP_INSTANCE_CREATE" ->
231
        OpCodes.OpInstanceCreate <$> genFQDN <*> arbitrary <*>
232
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
233
          pure emptyJSObject <*> arbitrary <*> arbitrary <*> arbitrary <*>
234
          genMaybe genNameNE <*> pure emptyJSObject <*> arbitrary <*>
235
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> arbitrary <*>
236
          arbitrary <*> arbitrary <*> arbitrary <*> pure emptyJSObject <*>
237
          genMaybe genNameNE <*> genMaybe genNodeNameNE <*> return Nothing <*>
238
          genMaybe genNodeNameNE <*> return Nothing <*> genMaybe (pure []) <*>
239
          genMaybe genNodeNameNE <*> arbitrary <*> genMaybe genNodeNameNE <*>
240
          return Nothing <*> genMaybe genNodeNameNE <*> genMaybe genNameNE <*>
241
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
242
      "OP_INSTANCE_MULTI_ALLOC" ->
243
        OpCodes.OpInstanceMultiAlloc <$> arbitrary <*> genMaybe genNameNE <*>
244
        pure []
245
      "OP_INSTANCE_REINSTALL" ->
246
        OpCodes.OpInstanceReinstall <$> genFQDN <*> return Nothing <*>
247
          arbitrary <*> genMaybe genNameNE <*> genMaybe (pure emptyJSObject)
248
      "OP_INSTANCE_REMOVE" ->
249
        OpCodes.OpInstanceRemove <$> genFQDN <*> return Nothing <*>
250
          arbitrary <*> arbitrary
251
      "OP_INSTANCE_RENAME" ->
252
        OpCodes.OpInstanceRename <$> genFQDN <*> return Nothing <*>
253
          genNodeNameNE <*> arbitrary <*> arbitrary
254
      "OP_INSTANCE_STARTUP" ->
255
        OpCodes.OpInstanceStartup <$> genFQDN <*> return Nothing <*>
256
          arbitrary <*> arbitrary <*> pure emptyJSObject <*>
257
          pure emptyJSObject <*> arbitrary <*> arbitrary
258
      "OP_INSTANCE_SHUTDOWN" ->
259
        OpCodes.OpInstanceShutdown <$> genFQDN <*> return Nothing <*>
260
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
261
      "OP_INSTANCE_REBOOT" ->
262
        OpCodes.OpInstanceReboot <$> genFQDN <*> return Nothing <*>
263
          arbitrary <*> arbitrary <*> arbitrary
264
      "OP_INSTANCE_MOVE" ->
265
        OpCodes.OpInstanceMove <$> genFQDN <*> return Nothing <*>
266
          arbitrary <*> arbitrary <*> genNodeNameNE <*> return Nothing <*>
267
          arbitrary
268
      "OP_INSTANCE_CONSOLE" -> OpCodes.OpInstanceConsole <$> genFQDN <*>
269
          return Nothing
270
      "OP_INSTANCE_ACTIVATE_DISKS" ->
271
        OpCodes.OpInstanceActivateDisks <$> genFQDN <*> return Nothing <*>
272
          arbitrary <*> arbitrary
273
      "OP_INSTANCE_DEACTIVATE_DISKS" ->
274
        OpCodes.OpInstanceDeactivateDisks <$> genFQDN <*> return Nothing <*>
275
          arbitrary
276
      "OP_INSTANCE_RECREATE_DISKS" ->
277
        OpCodes.OpInstanceRecreateDisks <$> genFQDN <*> return Nothing <*>
278
          arbitrary <*> genNodeNamesNE <*> return Nothing <*>
279
          genMaybe genNameNE
280
      "OP_INSTANCE_QUERY" ->
281
        OpCodes.OpInstanceQuery <$> genFieldsNE <*> arbitrary <*> genNamesNE
282
      "OP_INSTANCE_QUERY_DATA" ->
283
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
284
          genNodeNamesNE <*> arbitrary
285
      "OP_INSTANCE_SET_PARAMS" ->
286
        OpCodes.OpInstanceSetParams <$> genFQDN <*> return Nothing <*>
287
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
288
          arbitrary <*> pure emptyJSObject <*> arbitrary <*>
289
          pure emptyJSObject <*> arbitrary <*> genMaybe genNodeNameNE <*>
290
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
291
          genMaybe genNameNE <*> pure emptyJSObject <*> arbitrary <*>
292
          arbitrary <*> arbitrary
293
      "OP_INSTANCE_GROW_DISK" ->
294
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> return Nothing <*>
295
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
296
      "OP_INSTANCE_CHANGE_GROUP" ->
297
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> return Nothing <*>
298
          arbitrary <*> genMaybe genNameNE <*>
299
          genMaybe (resize maxNodes (listOf genNameNE))
300
      "OP_GROUP_ADD" ->
301
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
302
          emptyMUD <*> genMaybe genEmptyContainer <*>
303
          emptyMUD <*> emptyMUD <*> emptyMUD
304
      "OP_GROUP_ASSIGN_NODES" ->
305
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
306
          genNodeNamesNE <*> return Nothing
307
      "OP_GROUP_QUERY" ->
308
        OpCodes.OpGroupQuery <$> genFieldsNE <*> genNamesNE
309
      "OP_GROUP_SET_PARAMS" ->
310
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
311
          emptyMUD <*> genMaybe genEmptyContainer <*>
312
          emptyMUD <*> emptyMUD <*> emptyMUD
313
      "OP_GROUP_REMOVE" ->
314
        OpCodes.OpGroupRemove <$> genNameNE
315
      "OP_GROUP_RENAME" ->
316
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
317
      "OP_GROUP_EVACUATE" ->
318
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
319
          genMaybe genNameNE <*> genMaybe genNamesNE
320
      "OP_OS_DIAGNOSE" ->
321
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
322
      "OP_EXT_STORAGE_DIAGNOSE" ->
323
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
324
      "OP_BACKUP_QUERY" ->
325
        OpCodes.OpBackupQuery <$> arbitrary <*> genNodeNamesNE
326
      "OP_BACKUP_PREPARE" ->
327
        OpCodes.OpBackupPrepare <$> genFQDN <*> return Nothing <*> arbitrary
328
      "OP_BACKUP_EXPORT" ->
329
        OpCodes.OpBackupExport <$> genFQDN <*> return Nothing <*>
330
          arbitrary <*> arbitrary <*> return Nothing <*> arbitrary <*>
331
          arbitrary <*> arbitrary <*> arbitrary <*> genMaybe (pure []) <*>
332
          genMaybe genNameNE
333
      "OP_BACKUP_REMOVE" ->
334
        OpCodes.OpBackupRemove <$> genFQDN <*> return Nothing
335
      "OP_TEST_ALLOCATOR" ->
336
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
337
          genNameNE <*> genMaybe (pure []) <*> genMaybe (pure []) <*>
338
          arbitrary <*> genMaybe genNameNE <*>
339
          (genTags >>= mapM mkNonEmpty) <*>
340
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
341
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
342
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
343
      "OP_TEST_JQUEUE" ->
344
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
345
          resize 20 (listOf genFQDN) <*> arbitrary
346
      "OP_TEST_DUMMY" ->
347
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
348
          pure J.JSNull <*> pure J.JSNull
349
      "OP_NETWORK_ADD" ->
350
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIPv4Network <*>
351
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
352
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
353
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
354
      "OP_NETWORK_REMOVE" ->
355
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
356
      "OP_NETWORK_SET_PARAMS" ->
357
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
358
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
359
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
360
          genMaybe (listOf genIPv4Address)
361
      "OP_NETWORK_CONNECT" ->
362
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
363
          arbitrary <*> genNameNE <*> arbitrary
364
      "OP_NETWORK_DISCONNECT" ->
365
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
366
      "OP_NETWORK_QUERY" ->
367
        OpCodes.OpNetworkQuery <$> genFieldsNE <*> arbitrary <*> genNamesNE
368
      "OP_RESTRICTED_COMMAND" ->
369
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
370
          return Nothing <*> genNameNE
371
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
372

    
373
-- | Generates one element of a reason trail
374
genReasonElem :: Gen ReasonElem
375
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
376

    
377
-- | Generates a reason trail
378
genReasonTrail :: Gen ReasonTrail
379
genReasonTrail = do
380
  size <- choose (0, 10)
381
  vectorOf size genReasonElem
382

    
383
instance Arbitrary OpCodes.CommonOpParams where
384
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
385
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
386
                genReasonTrail
387

    
388
-- * Helper functions
389

    
390
-- | Empty JSObject.
391
emptyJSObject :: J.JSObject J.JSValue
392
emptyJSObject = J.toJSObject []
393

    
394
-- | Empty maybe unchecked dictionary.
395
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
396
emptyMUD = genMaybe $ pure emptyJSObject
397

    
398
-- | Generates an empty container.
399
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
400
genEmptyContainer = pure . GenericContainer $ Map.fromList []
401

    
402
-- | Generates list of disk indices.
403
genDiskIndices :: Gen [DiskIndex]
404
genDiskIndices = do
405
  cnt <- choose (0, C.maxDisks)
406
  genUniquesList cnt arbitrary
407

    
408
-- | Generates a list of node names.
409
genNodeNames :: Gen [String]
410
genNodeNames = resize maxNodes (listOf genFQDN)
411

    
412
-- | Generates a list of node names in non-empty string type.
413
genNodeNamesNE :: Gen [NonEmptyString]
414
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
415

    
416
-- | Gets a node name in non-empty type.
417
genNodeNameNE :: Gen NonEmptyString
418
genNodeNameNE = genFQDN >>= mkNonEmpty
419

    
420
-- | Gets a name (non-fqdn) in non-empty type.
421
genNameNE :: Gen NonEmptyString
422
genNameNE = genName >>= mkNonEmpty
423

    
424
-- | Gets a list of names (non-fqdn) in non-empty type.
425
genNamesNE :: Gen [NonEmptyString]
426
genNamesNE = resize maxNodes (listOf genNameNE)
427

    
428
-- | Returns a list of non-empty fields.
429
genFieldsNE :: Gen [NonEmptyString]
430
genFieldsNE = genFields >>= mapM mkNonEmpty
431

    
432
-- | Generate a 3-byte MAC prefix.
433
genMacPrefix :: Gen NonEmptyString
434
genMacPrefix = do
435
  octets <- vectorOf 3 $ choose (0::Int, 255)
436
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
437

    
438
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
439
$(genArbitrary ''OpCodes.MetaOpCode)
440

    
441
-- | Small helper to check for a failed JSON deserialisation
442
isJsonError :: J.Result a -> Bool
443
isJsonError (J.Error _) = True
444
isJsonError _           = False
445

    
446
-- * Test cases
447

    
448
-- | Check that opcode serialization is idempotent.
449
prop_serialization :: OpCodes.OpCode -> Property
450
prop_serialization = testSerialisation
451

    
452
-- | Check that Python and Haskell defined the same opcode list.
453
case_AllDefined :: HUnit.Assertion
454
case_AllDefined = do
455
  py_stdout <-
456
     runPython "from ganeti import opcodes\n\
457
               \from ganeti import serializer\n\
458
               \import sys\n\
459
               \print serializer.Dump([opid for opid in opcodes.OP_MAPPING])\n"
460
               ""
461
     >>= checkPythonResult
462
  py_ops <- case J.decode py_stdout::J.Result [String] of
463
               J.Ok ops -> return ops
464
               J.Error msg ->
465
                 HUnit.assertFailure ("Unable to decode opcode names: " ++ msg)
466
                 -- this already raised an expection, but we need it
467
                 -- for proper types
468
                 >> fail "Unable to decode opcode names"
469
  let hs_ops = sort OpCodes.allOpIDs
470
      extra_py = py_ops \\ hs_ops
471
      extra_hs = hs_ops \\ py_ops
472
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
473
                    unlines extra_py) (null extra_py)
474
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
475
                    unlines extra_hs) (null extra_hs)
476

    
477
-- | Custom HUnit test case that forks a Python process and checks
478
-- correspondence between Haskell-generated OpCodes and their Python
479
-- decoded, validated and re-encoded version.
480
--
481
-- Note that we have a strange beast here: since launching Python is
482
-- expensive, we don't do this via a usual QuickProperty, since that's
483
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
484
-- single HUnit assertion, and in it we manually use QuickCheck to
485
-- generate 500 opcodes times the number of defined opcodes, which
486
-- then we pass in bulk to Python. The drawbacks to this method are
487
-- two fold: we cannot control the number of generated opcodes, since
488
-- HUnit assertions don't get access to the test options, and for the
489
-- same reason we can't run a repeatable seed. We should probably find
490
-- a better way to do this, for example by having a
491
-- separately-launched Python process (if not running the tests would
492
-- be skipped).
493
case_py_compat_types :: HUnit.Assertion
494
case_py_compat_types = do
495
  let num_opcodes = length OpCodes.allOpIDs * 100
496
  opcodes <- genSample (vectorOf num_opcodes
497
                                   (arbitrary::Gen OpCodes.MetaOpCode))
498
  let with_sum = map (\o -> (OpCodes.opSummary $
499
                             OpCodes.metaOpCode o, o)) opcodes
500
      serialized = J.encode opcodes
501
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
502
  mapM_ (\op -> when (any (not . isAscii) (J.encode op)) .
503
                HUnit.assertFailure $
504
                  "OpCode has non-ASCII fields: " ++ show op
505
        ) opcodes
506
  py_stdout <-
507
     runPython "from ganeti import opcodes\n\
508
               \from ganeti import serializer\n\
509
               \import sys\n\
510
               \op_data = serializer.Load(sys.stdin.read())\n\
511
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
512
               \for op in decoded:\n\
513
               \  op.Validate(True)\n\
514
               \encoded = [(op.Summary(), op.__getstate__())\n\
515
               \           for op in decoded]\n\
516
               \print serializer.Dump(encoded)" serialized
517
     >>= checkPythonResult
518
  let deserialised =
519
        J.decode py_stdout::J.Result [(String, OpCodes.MetaOpCode)]
520
  decoded <- case deserialised of
521
               J.Ok ops -> return ops
522
               J.Error msg ->
523
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
524
                 -- this already raised an expection, but we need it
525
                 -- for proper types
526
                 >> fail "Unable to decode opcodes"
527
  HUnit.assertEqual "Mismatch in number of returned opcodes"
528
    (length decoded) (length with_sum)
529
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
530
        ) $ zip decoded with_sum
531

    
532
-- | Custom HUnit test case that forks a Python process and checks
533
-- correspondence between Haskell OpCodes fields and their Python
534
-- equivalent.
535
case_py_compat_fields :: HUnit.Assertion
536
case_py_compat_fields = do
537
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
538
                         OpCodes.allOpIDs
539
  py_stdout <-
540
     runPython "from ganeti import opcodes\n\
541
               \import sys\n\
542
               \from ganeti import serializer\n\
543
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
544
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
545
               \print serializer.Dump(fields)" ""
546
     >>= checkPythonResult
547
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
548
  py_fields <- case deserialised of
549
                 J.Ok v -> return $ sort v
550
                 J.Error msg ->
551
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
552
                   -- this already raised an expection, but we need it
553
                   -- for proper types
554
                   >> fail "Unable to decode op fields"
555
  HUnit.assertEqual "Mismatch in number of returned opcodes"
556
    (length hs_fields) (length py_fields)
557
  HUnit.assertEqual "Mismatch in defined OP_IDs"
558
    (map fst hs_fields) (map fst py_fields)
559
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
560
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
561
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
562
             py_flds hs_flds
563
        ) $ zip py_fields hs_fields
564

    
565
-- | Checks that setOpComment works correctly.
566
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
567
prop_setOpComment op comment =
568
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
569
  in OpCodes.opComment common ==? Just comment
570

    
571
-- | Tests wrong (negative) disk index.
572
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
573
prop_mkDiskIndex_fail (Positive i) =
574
  case mkDiskIndex (negate i) of
575
    Bad msg -> printTestCase "error message " $
576
               "Invalid value" `isPrefixOf` msg
577
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
578
                       "' from negative value " ++ show (negate i)
579

    
580
-- | Tests a few invalid 'readRecreateDisks' cases.
581
case_readRecreateDisks_fail :: Assertion
582
case_readRecreateDisks_fail = do
583
  assertBool "null" $
584
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
585
  assertBool "string" $
586
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
587

    
588
-- | Tests a few invalid 'readDdmOldChanges' cases.
589
case_readDdmOldChanges_fail :: Assertion
590
case_readDdmOldChanges_fail = do
591
  assertBool "null" $
592
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
593
  assertBool "string" $
594
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
595

    
596
-- | Tests a few invalid 'readExportTarget' cases.
597
case_readExportTarget_fail :: Assertion
598
case_readExportTarget_fail = do
599
  assertBool "null" $
600
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
601
  assertBool "int" $
602
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
603

    
604
testSuite "OpCodes"
605
            [ 'prop_serialization
606
            , 'case_AllDefined
607
            , 'case_py_compat_types
608
            , 'case_py_compat_fields
609
            , 'prop_setOpComment
610
            , 'prop_mkDiskIndex_fail
611
            , 'case_readRecreateDisks_fail
612
            , 'case_readDdmOldChanges_fail
613
            , 'case_readExportTarget_fail
614
            ]