Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 41f2bf8d

History | View | Annotate | Download (26.1 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 ISnapParams where
115
  arbitrary = ISnapParams <$> genNameNE
116

    
117
instance (Arbitrary a) => Arbitrary (SetSnapParams a) where
118
  arbitrary = oneof [ pure SetSnapParamsEmpty
119
                    , SetSnapParamsValid <$> arbitrary
120
                    ]
121

    
122
instance Arbitrary ExportTarget where
123
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
124
                    , ExportTargetRemote <$> pure []
125
                    ]
126

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

    
384
-- | Generates one element of a reason trail
385
genReasonElem :: Gen ReasonElem
386
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
387

    
388
-- | Generates a reason trail
389
genReasonTrail :: Gen ReasonTrail
390
genReasonTrail = do
391
  size <- choose (0, 10)
392
  vectorOf size genReasonElem
393

    
394
instance Arbitrary OpCodes.CommonOpParams where
395
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
396
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
397
                genReasonTrail
398

    
399
-- * Helper functions
400

    
401
-- | Empty JSObject.
402
emptyJSObject :: J.JSObject J.JSValue
403
emptyJSObject = J.toJSObject []
404

    
405
-- | Empty maybe unchecked dictionary.
406
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
407
emptyMUD = genMaybe $ pure emptyJSObject
408

    
409
-- | Generates an empty container.
410
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
411
genEmptyContainer = pure . GenericContainer $ Map.fromList []
412

    
413
-- | Generates list of disk indices.
414
genDiskIndices :: Gen [DiskIndex]
415
genDiskIndices = do
416
  cnt <- choose (0, C.maxDisks)
417
  genUniquesList cnt arbitrary
418

    
419
-- | Generates a list of node names.
420
genNodeNames :: Gen [String]
421
genNodeNames = resize maxNodes (listOf genFQDN)
422

    
423
-- | Generates a list of node names in non-empty string type.
424
genNodeNamesNE :: Gen [NonEmptyString]
425
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
426

    
427
-- | Gets a node name in non-empty type.
428
genNodeNameNE :: Gen NonEmptyString
429
genNodeNameNE = genFQDN >>= mkNonEmpty
430

    
431
-- | Gets a name (non-fqdn) in non-empty type.
432
genNameNE :: Gen NonEmptyString
433
genNameNE = genName >>= mkNonEmpty
434

    
435
-- | Gets a list of names (non-fqdn) in non-empty type.
436
genNamesNE :: Gen [NonEmptyString]
437
genNamesNE = resize maxNodes (listOf genNameNE)
438

    
439
-- | Returns a list of non-empty fields.
440
genFieldsNE :: Gen [NonEmptyString]
441
genFieldsNE = genFields >>= mapM mkNonEmpty
442

    
443
-- | Generate a 3-byte MAC prefix.
444
genMacPrefix :: Gen NonEmptyString
445
genMacPrefix = do
446
  octets <- vectorOf 3 $ choose (0::Int, 255)
447
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
448

    
449
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
450
$(genArbitrary ''OpCodes.MetaOpCode)
451

    
452
-- | Small helper to check for a failed JSON deserialisation
453
isJsonError :: J.Result a -> Bool
454
isJsonError (J.Error _) = True
455
isJsonError _           = False
456

    
457
-- * Test cases
458

    
459
-- | Check that opcode serialization is idempotent.
460
prop_serialization :: OpCodes.OpCode -> Property
461
prop_serialization = testSerialisation
462

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

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

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

    
576
-- | Checks that setOpComment works correctly.
577
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
578
prop_setOpComment op comment =
579
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
580
  in OpCodes.opComment common ==? Just comment
581

    
582
-- | Tests wrong (negative) disk index.
583
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
584
prop_mkDiskIndex_fail (Positive i) =
585
  case mkDiskIndex (negate i) of
586
    Bad msg -> printTestCase "error message " $
587
               "Invalid value" `isPrefixOf` msg
588
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
589
                       "' from negative value " ++ show (negate i)
590

    
591
-- | Tests a few invalid 'readRecreateDisks' cases.
592
case_readRecreateDisks_fail :: Assertion
593
case_readRecreateDisks_fail = do
594
  assertBool "null" $
595
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
596
  assertBool "string" $
597
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
598

    
599
-- | Tests a few invalid 'readDdmOldChanges' cases.
600
case_readDdmOldChanges_fail :: Assertion
601
case_readDdmOldChanges_fail = do
602
  assertBool "null" $
603
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
604
  assertBool "string" $
605
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
606

    
607
-- | Tests a few invalid 'readExportTarget' cases.
608
case_readExportTarget_fail :: Assertion
609
case_readExportTarget_fail = do
610
  assertBool "null" $
611
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
612
  assertBool "int" $
613
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
614

    
615
testSuite "OpCodes"
616
            [ 'prop_serialization
617
            , 'case_AllDefined
618
            , 'case_py_compat_types
619
            , 'case_py_compat_fields
620
            , 'prop_setOpComment
621
            , 'prop_mkDiskIndex_fail
622
            , 'case_readRecreateDisks_fail
623
            , 'case_readDdmOldChanges_fail
624
            , 'case_readExportTarget_fail
625
            ]