Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (23.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 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
$(genArbitrary ''InstReasonSrc)
73

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

    
77
instance Arbitrary INicParams where
78
  arbitrary = INicParams <$> genMaybe genNameNE <*> genMaybe genName <*>
79
              genMaybe genNameNE <*> genMaybe genNameNE
80

    
81
instance Arbitrary IDiskParams where
82
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
83
              genMaybe genNameNE <*> genMaybe genNameNE <*>
84
              genMaybe genNameNE
85

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

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

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

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

    
108
instance Arbitrary OpCodes.OpCode where
109
  arbitrary = do
110
    op_id <- elements OpCodes.allOpIDs
111
    case op_id of
112
      "OP_TEST_DELAY" ->
113
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary <*>
114
          genNodeNamesNE <*> arbitrary
115
      "OP_INSTANCE_REPLACE_DISKS" ->
116
        OpCodes.OpInstanceReplaceDisks <$> genFQDN <*> arbitrary <*>
117
          arbitrary <*> arbitrary <*> genDiskIndices <*>
118
          genMaybe genNodeNameNE <*> genMaybe genNameNE
119
      "OP_INSTANCE_FAILOVER" ->
120
        OpCodes.OpInstanceFailover <$> genFQDN <*> arbitrary <*> arbitrary <*>
121
          genMaybe genNodeNameNE <*> arbitrary <*> genMaybe genNameNE
122
      "OP_INSTANCE_MIGRATE" ->
123
        OpCodes.OpInstanceMigrate <$> genFQDN <*> arbitrary <*> arbitrary <*>
124
          genMaybe genNodeNameNE <*> arbitrary <*>
125
          arbitrary <*> arbitrary <*> 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 <$> 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
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 <*> arbitrary <*>
178
          arbitrary <*> arbitrary <*> (arbitrary `suchThat` (>0))
179
      "OP_NODE_REMOVE" -> OpCodes.OpNodeRemove <$> genNodeNameNE
180
      "OP_NODE_ADD" ->
181
        OpCodes.OpNodeAdd <$> genNodeNameNE <*> emptyMUD <*> emptyMUD <*>
182
          genMaybe genName <*> genMaybe genNameNE <*> arbitrary <*>
183
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> emptyMUD
184
      "OP_NODE_QUERY" ->
185
        OpCodes.OpNodeQuery <$> genFieldsNE <*> genNamesNE <*> arbitrary
186
      "OP_NODE_QUERYVOLS" ->
187
        OpCodes.OpNodeQueryvols <$> arbitrary <*> genNodeNamesNE
188
      "OP_NODE_QUERY_STORAGE" ->
189
        OpCodes.OpNodeQueryStorage <$> arbitrary <*> arbitrary <*>
190
          genNodeNamesNE <*> genNameNE
191
      "OP_NODE_MODIFY_STORAGE" ->
192
        OpCodes.OpNodeModifyStorage <$> genNodeNameNE <*> arbitrary <*>
193
          genNameNE <*> pure emptyJSObject
194
      "OP_REPAIR_NODE_STORAGE" ->
195
        OpCodes.OpRepairNodeStorage <$> genNodeNameNE <*> arbitrary <*>
196
          genNameNE <*> arbitrary
197
      "OP_NODE_SET_PARAMS" ->
198
        OpCodes.OpNodeSetParams <$> genNodeNameNE <*> arbitrary <*>
199
          emptyMUD <*> emptyMUD <*> arbitrary <*> arbitrary <*> arbitrary <*>
200
          arbitrary <*> arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
201
          emptyMUD <*> arbitrary
202
      "OP_NODE_POWERCYCLE" ->
203
        OpCodes.OpNodePowercycle <$> genNodeNameNE <*> arbitrary
204
      "OP_NODE_MIGRATE" ->
205
        OpCodes.OpNodeMigrate <$> genNodeNameNE <*> arbitrary <*>
206
          arbitrary <*> genMaybe genNodeNameNE <*> arbitrary <*>
207
          arbitrary <*> genMaybe genNameNE
208
      "OP_NODE_EVACUATE" ->
209
        OpCodes.OpNodeEvacuate <$> arbitrary <*> genNodeNameNE <*>
210
          genMaybe genNodeNameNE <*> genMaybe genNameNE <*> arbitrary
211
      "OP_INSTANCE_CREATE" ->
212
        OpCodes.OpInstanceCreate <$> genFQDN <*> arbitrary <*>
213
          arbitrary <*> arbitrary <*> arbitrary <*> pure emptyJSObject <*>
214
          arbitrary <*> arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
215
          pure emptyJSObject <*> arbitrary <*> genMaybe genNameNE <*>
216
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
217
          arbitrary <*> arbitrary <*> pure emptyJSObject <*>
218
          genMaybe genNameNE <*>
219
          genMaybe genNodeNameNE <*> genMaybe genNodeNameNE <*>
220
          genMaybe (pure []) <*> genMaybe genNodeNameNE <*>
221
          arbitrary <*> genMaybe genNodeNameNE <*>
222
          genMaybe genNodeNameNE <*> genMaybe genNameNE <*>
223
          arbitrary <*> arbitrary <*> (genTags >>= mapM mkNonEmpty)
224
      "OP_INSTANCE_MULTI_ALLOC" ->
225
        OpCodes.OpInstanceMultiAlloc <$> genMaybe genNameNE <*> pure [] <*>
226
          arbitrary
227
      "OP_INSTANCE_REINSTALL" ->
228
        OpCodes.OpInstanceReinstall <$> genFQDN <*> arbitrary <*>
229
          genMaybe genNameNE <*> genMaybe (pure emptyJSObject)
230
      "OP_INSTANCE_REMOVE" ->
231
        OpCodes.OpInstanceRemove <$> genFQDN <*> arbitrary <*> arbitrary
232
      "OP_INSTANCE_RENAME" ->
233
        OpCodes.OpInstanceRename <$> genFQDN <*> genNodeNameNE <*>
234
          arbitrary <*> arbitrary
235
      "OP_INSTANCE_STARTUP" ->
236
        OpCodes.OpInstanceStartup <$> genFQDN <*> arbitrary <*> arbitrary <*>
237
          pure emptyJSObject <*> pure emptyJSObject <*>
238
          arbitrary <*> arbitrary
239
      "OP_INSTANCE_SHUTDOWN" ->
240
        OpCodes.OpInstanceShutdown <$> genFQDN <*> arbitrary <*> arbitrary <*>
241
          arbitrary <*> arbitrary
242
      "OP_INSTANCE_REBOOT" ->
243
        OpCodes.OpInstanceReboot <$> genFQDN <*> arbitrary <*>
244
          arbitrary <*> arbitrary
245
      "OP_INSTANCE_MOVE" ->
246
        OpCodes.OpInstanceMove <$> genFQDN <*> arbitrary <*> arbitrary <*>
247
          genNodeNameNE <*> arbitrary
248
      "OP_INSTANCE_CONSOLE" -> OpCodes.OpInstanceConsole <$> genFQDN
249
      "OP_INSTANCE_ACTIVATE_DISKS" ->
250
        OpCodes.OpInstanceActivateDisks <$> genFQDN <*>
251
          arbitrary <*> arbitrary
252
      "OP_INSTANCE_DEACTIVATE_DISKS" ->
253
        OpCodes.OpInstanceDeactivateDisks <$> genFQDN <*> arbitrary
254
      "OP_INSTANCE_RECREATE_DISKS" ->
255
        OpCodes.OpInstanceRecreateDisks <$> genFQDN <*> arbitrary <*>
256
          genNodeNamesNE <*> genMaybe genNameNE
257
      "OP_INSTANCE_QUERY" ->
258
        OpCodes.OpInstanceQuery <$> genFieldsNE <*> genNamesNE <*> arbitrary
259
      "OP_INSTANCE_QUERY_DATA" ->
260
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
261
          genNodeNamesNE <*> arbitrary
262
      "OP_INSTANCE_SET_PARAMS" ->
263
        OpCodes.OpInstanceSetParams <$> genFQDN <*> arbitrary <*>
264
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
265
          pure emptyJSObject <*> arbitrary <*> pure emptyJSObject <*>
266
          arbitrary <*> genMaybe genNodeNameNE <*> genMaybe genNameNE <*>
267
          pure emptyJSObject <*> arbitrary <*> arbitrary <*> arbitrary
268
      "OP_INSTANCE_GROW_DISK" ->
269
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> arbitrary <*>
270
          arbitrary <*> arbitrary <*> arbitrary
271
      "OP_INSTANCE_CHANGE_GROUP" ->
272
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> arbitrary <*>
273
          genMaybe genNameNE <*> genMaybe (resize maxNodes (listOf genNameNE))
274
      "OP_GROUP_ADD" ->
275
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
276
          emptyMUD <*> genMaybe genEmptyContainer <*>
277
          emptyMUD <*> emptyMUD <*> emptyMUD
278
      "OP_GROUP_ASSIGN_NODES" ->
279
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
280
          genNodeNamesNE
281
      "OP_GROUP_QUERY" ->
282
        OpCodes.OpGroupQuery <$> genFieldsNE <*> genNamesNE
283
      "OP_GROUP_SET_PARAMS" ->
284
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
285
          emptyMUD <*> genMaybe genEmptyContainer <*>
286
          emptyMUD <*> emptyMUD <*> emptyMUD
287
      "OP_GROUP_REMOVE" ->
288
        OpCodes.OpGroupRemove <$> genNameNE
289
      "OP_GROUP_RENAME" ->
290
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
291
      "OP_GROUP_EVACUATE" ->
292
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
293
          genMaybe genNameNE <*> genMaybe genNamesNE
294
      "OP_OS_DIAGNOSE" ->
295
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
296
      "OP_EXT_STORAGE_DIAGNOSE" ->
297
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
298
      "OP_BACKUP_QUERY" ->
299
        OpCodes.OpBackupQuery <$> arbitrary <*> genNodeNamesNE
300
      "OP_BACKUP_PREPARE" ->
301
        OpCodes.OpBackupPrepare <$> genFQDN <*> arbitrary
302
      "OP_BACKUP_EXPORT" ->
303
        OpCodes.OpBackupExport <$> genFQDN <*> arbitrary <*>
304
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
305
          arbitrary <*> genMaybe (pure []) <*> genMaybe genNameNE
306
      "OP_BACKUP_REMOVE" ->
307
        OpCodes.OpBackupRemove <$> genFQDN
308
      "OP_TEST_ALLOCATOR" ->
309
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
310
          genNameNE <*> pure [] <*> pure [] <*>
311
          arbitrary <*> genMaybe genNameNE <*>
312
          (genTags >>= mapM mkNonEmpty) <*>
313
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
314
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
315
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
316
      "OP_TEST_JQUEUE" ->
317
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
318
          resize 20 (listOf genFQDN) <*> arbitrary
319
      "OP_TEST_DUMMY" ->
320
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
321
          pure J.JSNull <*> pure J.JSNull
322
      "OP_NETWORK_ADD" ->
323
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIp4Net <*>
324
          genMaybe genIp4Addr <*> pure Nothing <*> pure Nothing <*>
325
          genMaybe genMacPrefix <*> genMaybe (listOf genIp4Addr) <*>
326
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
327
      "OP_NETWORK_REMOVE" ->
328
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
329
      "OP_NETWORK_SET_PARAMS" ->
330
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
331
          genMaybe genIp4Addr <*> pure Nothing <*> pure Nothing <*>
332
          genMaybe genMacPrefix <*> genMaybe (listOf genIp4Addr) <*>
333
          genMaybe (listOf genIp4Addr)
334
      "OP_NETWORK_CONNECT" ->
335
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
336
          arbitrary <*> genNameNE <*> arbitrary
337
      "OP_NETWORK_DISCONNECT" ->
338
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
339
      "OP_NETWORK_QUERY" ->
340
        OpCodes.OpNetworkQuery <$> genFieldsNE <*> genNamesNE <*> arbitrary
341
      "OP_RESTRICTED_COMMAND" ->
342
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
343
          genNameNE
344
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
345

    
346
instance Arbitrary OpCodes.CommonOpParams where
347
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
348
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName
349

    
350
-- * Helper functions
351

    
352
-- | Empty JSObject.
353
emptyJSObject :: J.JSObject J.JSValue
354
emptyJSObject = J.toJSObject []
355

    
356
-- | Empty maybe unchecked dictionary.
357
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
358
emptyMUD = genMaybe $ pure emptyJSObject
359

    
360
-- | Generates an empty container.
361
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
362
genEmptyContainer = pure . GenericContainer $ Map.fromList []
363

    
364
-- | Generates list of disk indices.
365
genDiskIndices :: Gen [DiskIndex]
366
genDiskIndices = do
367
  cnt <- choose (0, C.maxDisks)
368
  genUniquesList cnt arbitrary
369

    
370
-- | Generates a list of node names.
371
genNodeNames :: Gen [String]
372
genNodeNames = resize maxNodes (listOf genFQDN)
373

    
374
-- | Generates a list of node names in non-empty string type.
375
genNodeNamesNE :: Gen [NonEmptyString]
376
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
377

    
378
-- | Gets a node name in non-empty type.
379
genNodeNameNE :: Gen NonEmptyString
380
genNodeNameNE = genFQDN >>= mkNonEmpty
381

    
382
-- | Gets a name (non-fqdn) in non-empty type.
383
genNameNE :: Gen NonEmptyString
384
genNameNE = genName >>= mkNonEmpty
385

    
386
-- | Gets a list of names (non-fqdn) in non-empty type.
387
genNamesNE :: Gen [NonEmptyString]
388
genNamesNE = resize maxNodes (listOf genNameNE)
389

    
390
-- | Returns a list of non-empty fields.
391
genFieldsNE :: Gen [NonEmptyString]
392
genFieldsNE = genFields >>= mapM mkNonEmpty
393

    
394
-- | Generate a 3-byte MAC prefix.
395
genMacPrefix :: Gen NonEmptyString
396
genMacPrefix = do
397
  octets <- vectorOf 3 $ choose (0::Int, 255)
398
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
399

    
400
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
401
$(genArbitrary ''OpCodes.MetaOpCode)
402

    
403
-- | Small helper to check for a failed JSON deserialisation
404
isJsonError :: J.Result a -> Bool
405
isJsonError (J.Error _) = True
406
isJsonError _           = False
407

    
408
-- * Test cases
409

    
410
-- | Check that opcode serialization is idempotent.
411
prop_serialization :: OpCodes.OpCode -> Property
412
prop_serialization = testSerialisation
413

    
414
-- | Check that Python and Haskell defined the same opcode list.
415
case_AllDefined :: HUnit.Assertion
416
case_AllDefined = do
417
  let py_ops = sort C.opcodesOpIds
418
      hs_ops = sort OpCodes.allOpIDs
419
      extra_py = py_ops \\ hs_ops
420
      extra_hs = hs_ops \\ py_ops
421
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
422
                    unlines extra_py) (null extra_py)
423
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
424
                    unlines extra_hs) (null extra_hs)
425

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

    
481
-- | Custom HUnit test case that forks a Python process and checks
482
-- correspondence between Haskell OpCodes fields and their Python
483
-- equivalent.
484
case_py_compat_fields :: HUnit.Assertion
485
case_py_compat_fields = do
486
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
487
                         OpCodes.allOpIDs
488
  py_stdout <-
489
     runPython "from ganeti import opcodes\n\
490
               \import sys\n\
491
               \from ganeti import serializer\n\
492
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
493
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
494
               \print serializer.Dump(fields)" ""
495
     >>= checkPythonResult
496
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
497
  py_fields <- case deserialised of
498
                 J.Ok v -> return $ sort v
499
                 J.Error msg ->
500
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
501
                   -- this already raised an expection, but we need it
502
                   -- for proper types
503
                   >> fail "Unable to decode op fields"
504
  HUnit.assertEqual "Mismatch in number of returned opcodes"
505
    (length hs_fields) (length py_fields)
506
  HUnit.assertEqual "Mismatch in defined OP_IDs"
507
    (map fst hs_fields) (map fst py_fields)
508
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
509
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
510
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
511
             py_flds hs_flds
512
        ) $ zip py_fields hs_fields
513

    
514
-- | Checks that setOpComment works correctly.
515
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
516
prop_setOpComment op comment =
517
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
518
  in OpCodes.opComment common ==? Just comment
519

    
520
-- | Tests wrong tag object building (cluster takes only jsnull, the
521
-- other take a string, so we test the opposites).
522
case_TagObject_fail :: Assertion
523
case_TagObject_fail =
524
  mapM_ (\(t, j) -> assertEqual (show t ++ "/" ++ J.encode j) Nothing $
525
                    tagObjectFrom t j)
526
    [ (TagTypeCluster,  J.showJSON "abc")
527
    , (TagTypeInstance, J.JSNull)
528
    , (TagTypeNode,     J.JSNull)
529
    , (TagTypeGroup,    J.JSNull)
530
    ]
531

    
532
-- | Tests wrong (negative) disk index.
533
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
534
prop_mkDiskIndex_fail (Positive i) =
535
  case mkDiskIndex (negate i) of
536
    Bad msg -> printTestCase "error message " $
537
               "Invalid value" `isPrefixOf` msg
538
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
539
                       "' from negative value " ++ show (negate i)
540

    
541
-- | Tests a few invalid 'readRecreateDisks' cases.
542
case_readRecreateDisks_fail :: Assertion
543
case_readRecreateDisks_fail = do
544
  assertBool "null" $
545
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
546
  assertBool "string" $
547
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
548

    
549
-- | Tests a few invalid 'readDdmOldChanges' cases.
550
case_readDdmOldChanges_fail :: Assertion
551
case_readDdmOldChanges_fail = do
552
  assertBool "null" $
553
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
554
  assertBool "string" $
555
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
556

    
557
-- | Tests a few invalid 'readExportTarget' cases.
558
case_readExportTarget_fail :: Assertion
559
case_readExportTarget_fail = do
560
  assertBool "null" $
561
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
562
  assertBool "int" $
563
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
564

    
565
testSuite "OpCodes"
566
            [ 'prop_serialization
567
            , 'case_AllDefined
568
            , 'case_py_compat_types
569
            , 'case_py_compat_fields
570
            , 'prop_setOpComment
571
            , 'case_TagObject_fail
572
            , 'prop_mkDiskIndex_fail
573
            , 'case_readRecreateDisks_fail
574
            , 'case_readDdmOldChanges_fail
575
            , 'case_readExportTarget_fail
576
            ]