Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 7002d873

History | View | Annotate | Download (25.2 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 Arbitrary OpCodes.TagObject where
62
  arbitrary = oneof [ OpCodes.TagInstance <$> genFQDN
63
                    , OpCodes.TagNode     <$> genFQDN
64
                    , OpCodes.TagGroup    <$> genFQDN
65
                    , pure OpCodes.TagCluster
66
                    ]
67

    
68
$(genArbitrary ''OpCodes.ReplaceDisksMode)
69

    
70
$(genArbitrary ''DiskAccess)
71

    
72
instance Arbitrary OpCodes.DiskIndex where
73
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
74

    
75
instance Arbitrary INicParams where
76
  arbitrary = INicParams <$> genMaybe genNameNE <*> genMaybe genName <*>
77
              genMaybe genNameNE <*> genMaybe genNameNE <*> genMaybe genNameNE
78

    
79
instance Arbitrary IDiskParams where
80
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
81
              genMaybe genNameNE <*> genMaybe genNameNE <*>
82
              genMaybe genNameNE <*> genMaybe genNameNE
83

    
84
instance Arbitrary RecreateDisksInfo where
85
  arbitrary = oneof [ pure RecreateDisksAll
86
                    , RecreateDisksIndices <$> arbitrary
87
                    , RecreateDisksParams <$> arbitrary
88
                    ]
89

    
90
instance Arbitrary DdmOldChanges where
91
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
92
                    , DdmOldMod   <$> arbitrary
93
                    ]
94

    
95
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
96
  arbitrary = oneof [ pure SetParamsEmpty
97
                    , SetParamsDeprecated <$> arbitrary
98
                    , SetParamsNew        <$> arbitrary
99
                    ]
100

    
101
instance Arbitrary ExportTarget where
102
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
103
                    , ExportTargetRemote <$> pure []
104
                    ]
105

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

    
360
-- | Generates one element of a reason trail
361
genReasonElem :: Gen ReasonElem
362
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
363

    
364
-- | Generates a reason trail
365
genReasonTrail :: Gen ReasonTrail
366
genReasonTrail = do
367
  size <- choose (0, 10)
368
  vectorOf size genReasonElem
369

    
370
instance Arbitrary OpCodes.CommonOpParams where
371
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
372
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
373
                genReasonTrail
374

    
375
-- * Helper functions
376

    
377
-- | Empty JSObject.
378
emptyJSObject :: J.JSObject J.JSValue
379
emptyJSObject = J.toJSObject []
380

    
381
-- | Empty maybe unchecked dictionary.
382
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
383
emptyMUD = genMaybe $ pure emptyJSObject
384

    
385
-- | Generates an empty container.
386
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
387
genEmptyContainer = pure . GenericContainer $ Map.fromList []
388

    
389
-- | Generates list of disk indices.
390
genDiskIndices :: Gen [DiskIndex]
391
genDiskIndices = do
392
  cnt <- choose (0, C.maxDisks)
393
  genUniquesList cnt arbitrary
394

    
395
-- | Generates a list of node names.
396
genNodeNames :: Gen [String]
397
genNodeNames = resize maxNodes (listOf genFQDN)
398

    
399
-- | Generates a list of node names in non-empty string type.
400
genNodeNamesNE :: Gen [NonEmptyString]
401
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
402

    
403
-- | Gets a node name in non-empty type.
404
genNodeNameNE :: Gen NonEmptyString
405
genNodeNameNE = genFQDN >>= mkNonEmpty
406

    
407
-- | Gets a name (non-fqdn) in non-empty type.
408
genNameNE :: Gen NonEmptyString
409
genNameNE = genName >>= mkNonEmpty
410

    
411
-- | Gets a list of names (non-fqdn) in non-empty type.
412
genNamesNE :: Gen [NonEmptyString]
413
genNamesNE = resize maxNodes (listOf genNameNE)
414

    
415
-- | Returns a list of non-empty fields.
416
genFieldsNE :: Gen [NonEmptyString]
417
genFieldsNE = genFields >>= mapM mkNonEmpty
418

    
419
-- | Generate a 3-byte MAC prefix.
420
genMacPrefix :: Gen NonEmptyString
421
genMacPrefix = do
422
  octets <- vectorOf 3 $ choose (0::Int, 255)
423
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
424

    
425
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
426
$(genArbitrary ''OpCodes.MetaOpCode)
427

    
428
-- | Small helper to check for a failed JSON deserialisation
429
isJsonError :: J.Result a -> Bool
430
isJsonError (J.Error _) = True
431
isJsonError _           = False
432

    
433
-- * Test cases
434

    
435
-- | Check that opcode serialization is idempotent.
436
prop_serialization :: OpCodes.OpCode -> Property
437
prop_serialization = testSerialisation
438

    
439
-- | Check that Python and Haskell defined the same opcode list.
440
case_AllDefined :: HUnit.Assertion
441
case_AllDefined = do
442
  let py_ops = sort C.opcodesOpIds
443
      hs_ops = sort OpCodes.allOpIDs
444
      extra_py = py_ops \\ hs_ops
445
      extra_hs = hs_ops \\ py_ops
446
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
447
                    unlines extra_py) (null extra_py)
448
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
449
                    unlines extra_hs) (null extra_hs)
450

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

    
506
-- | Custom HUnit test case that forks a Python process and checks
507
-- correspondence between Haskell OpCodes fields and their Python
508
-- equivalent.
509
case_py_compat_fields :: HUnit.Assertion
510
case_py_compat_fields = do
511
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
512
                         OpCodes.allOpIDs
513
  py_stdout <-
514
     runPython "from ganeti import opcodes\n\
515
               \import sys\n\
516
               \from ganeti import serializer\n\
517
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
518
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
519
               \print serializer.Dump(fields)" ""
520
     >>= checkPythonResult
521
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
522
  py_fields <- case deserialised of
523
                 J.Ok v -> return $ sort v
524
                 J.Error msg ->
525
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
526
                   -- this already raised an expection, but we need it
527
                   -- for proper types
528
                   >> fail "Unable to decode op fields"
529
  HUnit.assertEqual "Mismatch in number of returned opcodes"
530
    (length hs_fields) (length py_fields)
531
  HUnit.assertEqual "Mismatch in defined OP_IDs"
532
    (map fst hs_fields) (map fst py_fields)
533
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
534
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
535
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
536
             py_flds hs_flds
537
        ) $ zip py_fields hs_fields
538

    
539
-- | Checks that setOpComment works correctly.
540
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
541
prop_setOpComment op comment =
542
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
543
  in OpCodes.opComment common ==? Just comment
544

    
545
-- | Tests wrong tag object building (cluster takes only jsnull, the
546
-- other take a string, so we test the opposites).
547
case_TagObject_fail :: Assertion
548
case_TagObject_fail =
549
  mapM_ (\(t, j) -> assertEqual (show t ++ "/" ++ J.encode j) Nothing $
550
                    tagObjectFrom t j)
551
    [ (TagTypeCluster,  J.showJSON "abc")
552
    , (TagTypeInstance, J.JSNull)
553
    , (TagTypeNode,     J.JSNull)
554
    , (TagTypeGroup,    J.JSNull)
555
    ]
556

    
557
-- | Tests wrong (negative) disk index.
558
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
559
prop_mkDiskIndex_fail (Positive i) =
560
  case mkDiskIndex (negate i) of
561
    Bad msg -> printTestCase "error message " $
562
               "Invalid value" `isPrefixOf` msg
563
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
564
                       "' from negative value " ++ show (negate i)
565

    
566
-- | Tests a few invalid 'readRecreateDisks' cases.
567
case_readRecreateDisks_fail :: Assertion
568
case_readRecreateDisks_fail = do
569
  assertBool "null" $
570
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
571
  assertBool "string" $
572
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
573

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

    
582
-- | Tests a few invalid 'readExportTarget' cases.
583
case_readExportTarget_fail :: Assertion
584
case_readExportTarget_fail = do
585
  assertBool "null" $
586
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
587
  assertBool "int" $
588
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
589

    
590
testSuite "OpCodes"
591
            [ 'prop_serialization
592
            , 'case_AllDefined
593
            , 'case_py_compat_types
594
            , 'case_py_compat_fields
595
            , 'prop_setOpComment
596
            , 'case_TagObject_fail
597
            , 'prop_mkDiskIndex_fail
598
            , 'case_readRecreateDisks_fail
599
            , 'case_readDdmOldChanges_fail
600
            , 'case_readExportTarget_fail
601
            ]