Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (24.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 Arbitrary OpCodes.TagObject where
62
  arbitrary = oneof [ OpCodes.TagInstance <$> genFQDN
63
                    , OpCodes.TagNode     <$> genFQDN
64
                    , OpCodes.TagGroup    <$> genFQDN
65
                    , pure OpCodes.TagCluster
66
                    ]
67

    
68
$(genArbitrary ''OpCodes.ReplaceDisksMode)
69

    
70
$(genArbitrary ''DiskAccess)
71

    
72
instance Arbitrary OpCodes.DiskIndex where
73
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
74

    
75
instance Arbitrary INicParams where
76
  arbitrary = INicParams <$> genMaybe genNameNE <*> genMaybe genName <*>
77
              genMaybe genNameNE <*> genMaybe genNameNE <*> genMaybe genNameNE
78

    
79
instance Arbitrary IDiskParams where
80
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
81
              genMaybe genNameNE <*> genMaybe genNameNE <*>
82
              genMaybe genNameNE <*> genMaybe genNameNE
83

    
84
instance Arbitrary RecreateDisksInfo where
85
  arbitrary = oneof [ pure RecreateDisksAll
86
                    , RecreateDisksIndices <$> arbitrary
87
                    , RecreateDisksParams <$> arbitrary
88
                    ]
89

    
90
instance Arbitrary DdmOldChanges where
91
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
92
                    , DdmOldMod   <$> arbitrary
93
                    ]
94

    
95
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
96
  arbitrary = oneof [ pure SetParamsEmpty
97
                    , SetParamsDeprecated <$> arbitrary
98
                    , SetParamsNew        <$> arbitrary
99
                    ]
100

    
101
instance Arbitrary ISnapParams where
102
  arbitrary = ISnapParams <$> genNameNE
103

    
104
instance (Arbitrary a) => Arbitrary (SetSnapParams a) where
105
  arbitrary = oneof [ pure SetSnapParamsEmpty
106
                    , SetSnapParamsValid <$> arbitrary
107
                    ]
108

    
109
instance Arbitrary ExportTarget where
110
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
111
                    , ExportTargetRemote <$> pure []
112
                    ]
113

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

    
357
-- | Generates one element of a reason trail
358
genReasonElem :: Gen ReasonElem
359
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
360

    
361
-- | Generates a reason trail
362
genReasonTrail :: Gen ReasonTrail
363
genReasonTrail = do
364
  size <- choose (0, 10)
365
  vectorOf size genReasonElem
366

    
367
instance Arbitrary OpCodes.CommonOpParams where
368
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
369
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
370
                genReasonTrail
371

    
372
-- * Helper functions
373

    
374
-- | Empty JSObject.
375
emptyJSObject :: J.JSObject J.JSValue
376
emptyJSObject = J.toJSObject []
377

    
378
-- | Empty maybe unchecked dictionary.
379
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
380
emptyMUD = genMaybe $ pure emptyJSObject
381

    
382
-- | Generates an empty container.
383
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
384
genEmptyContainer = pure . GenericContainer $ Map.fromList []
385

    
386
-- | Generates list of disk indices.
387
genDiskIndices :: Gen [DiskIndex]
388
genDiskIndices = do
389
  cnt <- choose (0, C.maxDisks)
390
  genUniquesList cnt arbitrary
391

    
392
-- | Generates a list of node names.
393
genNodeNames :: Gen [String]
394
genNodeNames = resize maxNodes (listOf genFQDN)
395

    
396
-- | Generates a list of node names in non-empty string type.
397
genNodeNamesNE :: Gen [NonEmptyString]
398
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
399

    
400
-- | Gets a node name in non-empty type.
401
genNodeNameNE :: Gen NonEmptyString
402
genNodeNameNE = genFQDN >>= mkNonEmpty
403

    
404
-- | Gets a name (non-fqdn) in non-empty type.
405
genNameNE :: Gen NonEmptyString
406
genNameNE = genName >>= mkNonEmpty
407

    
408
-- | Gets a list of names (non-fqdn) in non-empty type.
409
genNamesNE :: Gen [NonEmptyString]
410
genNamesNE = resize maxNodes (listOf genNameNE)
411

    
412
-- | Returns a list of non-empty fields.
413
genFieldsNE :: Gen [NonEmptyString]
414
genFieldsNE = genFields >>= mapM mkNonEmpty
415

    
416
-- | Generate a 3-byte MAC prefix.
417
genMacPrefix :: Gen NonEmptyString
418
genMacPrefix = do
419
  octets <- vectorOf 3 $ choose (0::Int, 255)
420
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
421

    
422
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
423
$(genArbitrary ''OpCodes.MetaOpCode)
424

    
425
-- | Small helper to check for a failed JSON deserialisation
426
isJsonError :: J.Result a -> Bool
427
isJsonError (J.Error _) = True
428
isJsonError _           = False
429

    
430
-- * Test cases
431

    
432
-- | Check that opcode serialization is idempotent.
433
prop_serialization :: OpCodes.OpCode -> Property
434
prop_serialization = testSerialisation
435

    
436
-- | Check that Python and Haskell defined the same opcode list.
437
case_AllDefined :: HUnit.Assertion
438
case_AllDefined = do
439
  let py_ops = sort C.opcodesOpIds
440
      hs_ops = sort OpCodes.allOpIDs
441
      extra_py = py_ops \\ hs_ops
442
      extra_hs = hs_ops \\ py_ops
443
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
444
                    unlines extra_py) (null extra_py)
445
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
446
                    unlines extra_hs) (null extra_hs)
447

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

    
503
-- | Custom HUnit test case that forks a Python process and checks
504
-- correspondence between Haskell OpCodes fields and their Python
505
-- equivalent.
506
case_py_compat_fields :: HUnit.Assertion
507
case_py_compat_fields = do
508
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
509
                         OpCodes.allOpIDs
510
  py_stdout <-
511
     runPython "from ganeti import opcodes\n\
512
               \import sys\n\
513
               \from ganeti import serializer\n\
514
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
515
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
516
               \print serializer.Dump(fields)" ""
517
     >>= checkPythonResult
518
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
519
  py_fields <- case deserialised of
520
                 J.Ok v -> return $ sort v
521
                 J.Error msg ->
522
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
523
                   -- this already raised an expection, but we need it
524
                   -- for proper types
525
                   >> fail "Unable to decode op fields"
526
  HUnit.assertEqual "Mismatch in number of returned opcodes"
527
    (length hs_fields) (length py_fields)
528
  HUnit.assertEqual "Mismatch in defined OP_IDs"
529
    (map fst hs_fields) (map fst py_fields)
530
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
531
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
532
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
533
             py_flds hs_flds
534
        ) $ zip py_fields hs_fields
535

    
536
-- | Checks that setOpComment works correctly.
537
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
538
prop_setOpComment op comment =
539
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
540
  in OpCodes.opComment common ==? Just comment
541

    
542
-- | Tests wrong tag object building (cluster takes only jsnull, the
543
-- other take a string, so we test the opposites).
544
case_TagObject_fail :: Assertion
545
case_TagObject_fail =
546
  mapM_ (\(t, j) -> assertEqual (show t ++ "/" ++ J.encode j) Nothing $
547
                    tagObjectFrom t j)
548
    [ (TagTypeCluster,  J.showJSON "abc")
549
    , (TagTypeInstance, J.JSNull)
550
    , (TagTypeNode,     J.JSNull)
551
    , (TagTypeGroup,    J.JSNull)
552
    ]
553

    
554
-- | Tests wrong (negative) disk index.
555
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
556
prop_mkDiskIndex_fail (Positive i) =
557
  case mkDiskIndex (negate i) of
558
    Bad msg -> printTestCase "error message " $
559
               "Invalid value" `isPrefixOf` msg
560
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
561
                       "' from negative value " ++ show (negate i)
562

    
563
-- | Tests a few invalid 'readRecreateDisks' cases.
564
case_readRecreateDisks_fail :: Assertion
565
case_readRecreateDisks_fail = do
566
  assertBool "null" $
567
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
568
  assertBool "string" $
569
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
570

    
571
-- | Tests a few invalid 'readDdmOldChanges' cases.
572
case_readDdmOldChanges_fail :: Assertion
573
case_readDdmOldChanges_fail = do
574
  assertBool "null" $
575
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
576
  assertBool "string" $
577
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
578

    
579
-- | Tests a few invalid 'readExportTarget' cases.
580
case_readExportTarget_fail :: Assertion
581
case_readExportTarget_fail = do
582
  assertBool "null" $
583
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
584
  assertBool "int" $
585
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
586

    
587
testSuite "OpCodes"
588
            [ 'prop_serialization
589
            , 'case_AllDefined
590
            , 'case_py_compat_types
591
            , 'case_py_compat_fields
592
            , 'prop_setOpComment
593
            , 'case_TagObject_fail
594
            , 'prop_mkDiskIndex_fail
595
            , 'case_readRecreateDisks_fail
596
            , 'case_readDdmOldChanges_fail
597
            , 'case_readExportTarget_fail
598
            ]