Statistics
| Branch: | Tag: | Revision:

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

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

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

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

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

    
381
-- * Helper functions
382

    
383
-- | Empty JSObject.
384
emptyJSObject :: J.JSObject J.JSValue
385
emptyJSObject = J.toJSObject []
386

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

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

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

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

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

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

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

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

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

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

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

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

    
439
-- * Test cases
440

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

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

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

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

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

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

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

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

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

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