Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (25.8 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 genNameNE <*>
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

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

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

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

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

    
121
instance Arbitrary OpCodes.OpCode where
122
  arbitrary = do
123
    op_id <- elements OpCodes.allOpIDs
124
    case op_id of
125
      "OP_TEST_DELAY" ->
126
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary <*>
127
          genNodeNamesNE <*> return Nothing <*> arbitrary
128
      "OP_INSTANCE_REPLACE_DISKS" ->
129
        OpCodes.OpInstanceReplaceDisks <$> genFQDN <*> return Nothing <*>
130
          arbitrary <*> arbitrary <*> arbitrary <*> genDiskIndices <*>
131
          genMaybe genNodeNameNE <*> return Nothing <*> genMaybe genNameNE
132
      "OP_INSTANCE_FAILOVER" ->
133
        OpCodes.OpInstanceFailover <$> genFQDN <*> return Nothing <*>
134
        arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
135
        return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
136
      "OP_INSTANCE_MIGRATE" ->
137
        OpCodes.OpInstanceMigrate <$> genFQDN <*> return Nothing <*>
138
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
139
          return Nothing <*> arbitrary <*> arbitrary <*> arbitrary <*>
140
          genMaybe genNameNE <*> arbitrary
141
      "OP_TAGS_GET" ->
142
        arbitraryOpTagsGet
143
      "OP_TAGS_SEARCH" ->
144
        OpCodes.OpTagsSearch <$> genNameNE
145
      "OP_TAGS_SET" ->
146
        arbitraryOpTagsSet
147
      "OP_TAGS_DEL" ->
148
        arbitraryOpTagsDel
149
      "OP_CLUSTER_POST_INIT" -> pure OpCodes.OpClusterPostInit
150
      "OP_CLUSTER_DESTROY" -> pure OpCodes.OpClusterDestroy
151
      "OP_CLUSTER_QUERY" -> pure OpCodes.OpClusterQuery
152
      "OP_CLUSTER_VERIFY" ->
153
        OpCodes.OpClusterVerify <$> arbitrary <*> arbitrary <*>
154
          genListSet Nothing <*> genListSet Nothing <*> arbitrary <*>
155
          genMaybe genNameNE
156
      "OP_CLUSTER_VERIFY_CONFIG" ->
157
        OpCodes.OpClusterVerifyConfig <$> arbitrary <*> arbitrary <*>
158
          genListSet Nothing <*> arbitrary
159
      "OP_CLUSTER_VERIFY_GROUP" ->
160
        OpCodes.OpClusterVerifyGroup <$> genNameNE <*> arbitrary <*>
161
          arbitrary <*> genListSet Nothing <*> genListSet Nothing <*> arbitrary
162
      "OP_CLUSTER_VERIFY_DISKS" -> pure OpCodes.OpClusterVerifyDisks
163
      "OP_GROUP_VERIFY_DISKS" ->
164
        OpCodes.OpGroupVerifyDisks <$> genNameNE
165
      "OP_CLUSTER_REPAIR_DISK_SIZES" ->
166
        OpCodes.OpClusterRepairDiskSizes <$> genNodeNamesNE
167
      "OP_CLUSTER_CONFIG_QUERY" ->
168
        OpCodes.OpClusterConfigQuery <$> genFieldsNE
169
      "OP_CLUSTER_RENAME" ->
170
        OpCodes.OpClusterRename <$> genNameNE
171
      "OP_CLUSTER_SET_PARAMS" ->
172
        OpCodes.OpClusterSetParams <$> arbitrary <*> emptyMUD <*> emptyMUD <*>
173
          arbitrary <*> genMaybe arbitrary <*>
174
          genMaybe genEmptyContainer <*> emptyMUD <*>
175
          genMaybe genEmptyContainer <*> genMaybe genEmptyContainer <*>
176
          genMaybe genEmptyContainer <*> genMaybe arbitrary <*>
177
          arbitrary <*> arbitrary <*> arbitrary <*>
178
          arbitrary <*> arbitrary <*> arbitrary <*>
179
          emptyMUD <*> emptyMUD <*> arbitrary <*>
180
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
181
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
182
          genMaybe genName <*>
183
          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_QUERY" ->
205
        OpCodes.OpNodeQuery <$> genFieldsNE <*> genNamesNE <*> arbitrary
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 <*> (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" ->
284
        OpCodes.OpInstanceQuery <$> genFieldsNE <*> arbitrary <*> genNamesNE
285
      "OP_INSTANCE_QUERY_DATA" ->
286
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
287
          genNodeNamesNE <*> arbitrary
288
      "OP_INSTANCE_SET_PARAMS" ->
289
        OpCodes.OpInstanceSetParams <$> genFQDN <*> return Nothing <*>
290
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
291
          arbitrary <*> pure emptyJSObject <*> arbitrary <*>
292
          pure emptyJSObject <*> arbitrary <*> genMaybe genNodeNameNE <*>
293
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
294
          genMaybe genNameNE <*> pure emptyJSObject <*> arbitrary <*>
295
          arbitrary <*> arbitrary
296
      "OP_INSTANCE_GROW_DISK" ->
297
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> return Nothing <*>
298
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
299
      "OP_INSTANCE_CHANGE_GROUP" ->
300
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> return Nothing <*>
301
          arbitrary <*> genMaybe genNameNE <*>
302
          genMaybe (resize maxNodes (listOf genNameNE))
303
      "OP_GROUP_ADD" ->
304
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
305
          emptyMUD <*> genMaybe genEmptyContainer <*>
306
          emptyMUD <*> emptyMUD <*> emptyMUD
307
      "OP_GROUP_ASSIGN_NODES" ->
308
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
309
          genNodeNamesNE <*> return Nothing
310
      "OP_GROUP_QUERY" ->
311
        OpCodes.OpGroupQuery <$> genFieldsNE <*> genNamesNE
312
      "OP_GROUP_SET_PARAMS" ->
313
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
314
          emptyMUD <*> genMaybe genEmptyContainer <*>
315
          emptyMUD <*> emptyMUD <*> emptyMUD
316
      "OP_GROUP_REMOVE" ->
317
        OpCodes.OpGroupRemove <$> genNameNE
318
      "OP_GROUP_RENAME" ->
319
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
320
      "OP_GROUP_EVACUATE" ->
321
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
322
          genMaybe genNameNE <*> genMaybe genNamesNE
323
      "OP_OS_DIAGNOSE" ->
324
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
325
      "OP_EXT_STORAGE_DIAGNOSE" ->
326
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
327
      "OP_BACKUP_QUERY" ->
328
        OpCodes.OpBackupQuery <$> arbitrary <*> genNodeNamesNE
329
      "OP_BACKUP_PREPARE" ->
330
        OpCodes.OpBackupPrepare <$> genFQDN <*> return Nothing <*> arbitrary
331
      "OP_BACKUP_EXPORT" ->
332
        OpCodes.OpBackupExport <$> genFQDN <*> return Nothing <*>
333
          arbitrary <*> arbitrary <*> return Nothing <*> arbitrary <*>
334
          arbitrary <*> arbitrary <*> arbitrary <*> genMaybe (pure []) <*>
335
          genMaybe genNameNE
336
      "OP_BACKUP_REMOVE" ->
337
        OpCodes.OpBackupRemove <$> genFQDN <*> return Nothing
338
      "OP_TEST_ALLOCATOR" ->
339
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
340
          genNameNE <*> genMaybe (pure []) <*> genMaybe (pure []) <*>
341
          arbitrary <*> genMaybe genNameNE <*>
342
          (genTags >>= mapM mkNonEmpty) <*>
343
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
344
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
345
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
346
      "OP_TEST_JQUEUE" ->
347
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
348
          resize 20 (listOf genFQDN) <*> arbitrary
349
      "OP_TEST_DUMMY" ->
350
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
351
          pure J.JSNull <*> pure J.JSNull
352
      "OP_NETWORK_ADD" ->
353
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIPv4Network <*>
354
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
355
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
356
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
357
      "OP_NETWORK_REMOVE" ->
358
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
359
      "OP_NETWORK_SET_PARAMS" ->
360
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
361
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
362
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
363
          genMaybe (listOf genIPv4Address)
364
      "OP_NETWORK_CONNECT" ->
365
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
366
          arbitrary <*> genNameNE <*> arbitrary
367
      "OP_NETWORK_DISCONNECT" ->
368
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
369
      "OP_NETWORK_QUERY" ->
370
        OpCodes.OpNetworkQuery <$> genFieldsNE <*> arbitrary <*> genNamesNE
371
      "OP_RESTRICTED_COMMAND" ->
372
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
373
          return Nothing <*> genNameNE
374
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
375

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

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

    
386
instance Arbitrary OpCodes.CommonOpParams where
387
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
388
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
389
                genReasonTrail
390

    
391
-- * Helper functions
392

    
393
-- | Empty JSObject.
394
emptyJSObject :: J.JSObject J.JSValue
395
emptyJSObject = J.toJSObject []
396

    
397
-- | Empty maybe unchecked dictionary.
398
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
399
emptyMUD = genMaybe $ pure emptyJSObject
400

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

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

    
411
-- | Generates a list of node names.
412
genNodeNames :: Gen [String]
413
genNodeNames = resize maxNodes (listOf genFQDN)
414

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

    
419
-- | Gets a node name in non-empty type.
420
genNodeNameNE :: Gen NonEmptyString
421
genNodeNameNE = genFQDN >>= mkNonEmpty
422

    
423
-- | Gets a name (non-fqdn) in non-empty type.
424
genNameNE :: Gen NonEmptyString
425
genNameNE = genName >>= mkNonEmpty
426

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

    
431
-- | Returns a list of non-empty fields.
432
genFieldsNE :: Gen [NonEmptyString]
433
genFieldsNE = genFields >>= mapM mkNonEmpty
434

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

    
441
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
442
$(genArbitrary ''OpCodes.MetaOpCode)
443

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

    
449
-- * Test cases
450

    
451
-- | Check that opcode serialization is idempotent.
452
prop_serialization :: OpCodes.OpCode -> Property
453
prop_serialization = testSerialisation
454

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

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

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

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

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

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

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

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

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