Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 0359e5d0

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

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

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

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

    
382
-- * Helper functions
383

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

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

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

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

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

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

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

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

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

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

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

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

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

    
440
-- * Test cases
441

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

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

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

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

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

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

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

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

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

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