Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (25.5 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
$(genArbitrary ''ImportExportCompression)
84

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

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

    
94
instance Arbitrary IDiskParams where
95
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
96
              genMaybe genNameNE <*> genMaybe genNameNE <*>
97
              genMaybe genNameNE <*> genMaybe genNameNE <*>
98
              genMaybe genNameNE <*> arbitrary
99

    
100
instance Arbitrary RecreateDisksInfo where
101
  arbitrary = oneof [ pure RecreateDisksAll
102
                    , RecreateDisksIndices <$> arbitrary
103
                    , RecreateDisksParams <$> arbitrary
104
                    ]
105

    
106
instance Arbitrary DdmOldChanges where
107
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
108
                    , DdmOldMod   <$> arbitrary
109
                    ]
110

    
111
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
112
  arbitrary = oneof [ pure SetParamsEmpty
113
                    , SetParamsDeprecated <$> arbitrary
114
                    , SetParamsNew        <$> arbitrary
115
                    ]
116

    
117
instance Arbitrary ExportTarget where
118
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
119
                    , ExportTargetRemote <$> pure []
120
                    ]
121

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

    
368
-- | Generates one element of a reason trail
369
genReasonElem :: Gen ReasonElem
370
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
371

    
372
-- | Generates a reason trail
373
genReasonTrail :: Gen ReasonTrail
374
genReasonTrail = do
375
  size <- choose (0, 10)
376
  vectorOf size genReasonElem
377

    
378
instance Arbitrary OpCodes.CommonOpParams where
379
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
380
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
381
                genReasonTrail
382

    
383
-- * Helper functions
384

    
385
-- | Empty JSObject.
386
emptyJSObject :: J.JSObject J.JSValue
387
emptyJSObject = J.toJSObject []
388

    
389
-- | Empty maybe unchecked dictionary.
390
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
391
emptyMUD = genMaybe $ pure emptyJSObject
392

    
393
-- | Generates an empty container.
394
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
395
genEmptyContainer = pure . GenericContainer $ Map.fromList []
396

    
397
-- | Generates list of disk indices.
398
genDiskIndices :: Gen [DiskIndex]
399
genDiskIndices = do
400
  cnt <- choose (0, C.maxDisks)
401
  genUniquesList cnt arbitrary
402

    
403
-- | Generates a list of node names.
404
genNodeNames :: Gen [String]
405
genNodeNames = resize maxNodes (listOf genFQDN)
406

    
407
-- | Generates a list of node names in non-empty string type.
408
genNodeNamesNE :: Gen [NonEmptyString]
409
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
410

    
411
-- | Gets a node name in non-empty type.
412
genNodeNameNE :: Gen NonEmptyString
413
genNodeNameNE = genFQDN >>= mkNonEmpty
414

    
415
-- | Gets a name (non-fqdn) in non-empty type.
416
genNameNE :: Gen NonEmptyString
417
genNameNE = genName >>= mkNonEmpty
418

    
419
-- | Gets a list of names (non-fqdn) in non-empty type.
420
genNamesNE :: Gen [NonEmptyString]
421
genNamesNE = resize maxNodes (listOf genNameNE)
422

    
423
-- | Returns a list of non-empty fields.
424
genFieldsNE :: Gen [NonEmptyString]
425
genFieldsNE = genFields >>= mapM mkNonEmpty
426

    
427
-- | Generate a 3-byte MAC prefix.
428
genMacPrefix :: Gen NonEmptyString
429
genMacPrefix = do
430
  octets <- vectorOf 3 $ choose (0::Int, 255)
431
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
432

    
433
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
434
$(genArbitrary ''OpCodes.MetaOpCode)
435

    
436
-- | Small helper to check for a failed JSON deserialisation
437
isJsonError :: J.Result a -> Bool
438
isJsonError (J.Error _) = True
439
isJsonError _           = False
440

    
441
-- * Test cases
442

    
443
-- | Check that opcode serialization is idempotent.
444
prop_serialization :: OpCodes.OpCode -> Property
445
prop_serialization = testSerialisation
446

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

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

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

    
560
-- | Checks that setOpComment works correctly.
561
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
562
prop_setOpComment op comment =
563
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
564
  in OpCodes.opComment common ==? Just comment
565

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

    
575
-- | Tests a few invalid 'readRecreateDisks' cases.
576
case_readRecreateDisks_fail :: Assertion
577
case_readRecreateDisks_fail = do
578
  assertBool "null" $
579
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
580
  assertBool "string" $
581
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
582

    
583
-- | Tests a few invalid 'readDdmOldChanges' cases.
584
case_readDdmOldChanges_fail :: Assertion
585
case_readDdmOldChanges_fail = do
586
  assertBool "null" $
587
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
588
  assertBool "string" $
589
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
590

    
591
-- | Tests a few invalid 'readExportTarget' cases.
592
case_readExportTarget_fail :: Assertion
593
case_readExportTarget_fail = do
594
  assertBool "null" $
595
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
596
  assertBool "int" $
597
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
598

    
599
testSuite "OpCodes"
600
            [ 'prop_serialization
601
            , 'case_AllDefined
602
            , 'case_py_compat_types
603
            , 'case_py_compat_fields
604
            , 'prop_setOpComment
605
            , 'prop_mkDiskIndex_fail
606
            , 'case_readRecreateDisks_fail
607
            , 'case_readDdmOldChanges_fail
608
            , 'case_readExportTarget_fail
609
            ]