Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 6bce7ba2

History | View | Annotate | Download (29.9 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
              genMaybe genNameNE <*> arbitrary <*> genAndRestArguments
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_RENEW_CRYPTO" -> pure OpCodes.OpClusterRenewCrypto
152
      "OP_CLUSTER_DESTROY" -> pure OpCodes.OpClusterDestroy
153
      "OP_CLUSTER_QUERY" -> pure OpCodes.OpClusterQuery
154
      "OP_CLUSTER_VERIFY" ->
155
        OpCodes.OpClusterVerify <$> arbitrary <*> arbitrary <*>
156
          genListSet Nothing <*> genListSet Nothing <*> arbitrary <*>
157
          genMaybe genNameNE
158
      "OP_CLUSTER_VERIFY_CONFIG" ->
159
        OpCodes.OpClusterVerifyConfig <$> arbitrary <*> arbitrary <*>
160
          genListSet Nothing <*> arbitrary
161
      "OP_CLUSTER_VERIFY_GROUP" ->
162
        OpCodes.OpClusterVerifyGroup <$> genNameNE <*> arbitrary <*>
163
          arbitrary <*> genListSet Nothing <*> genListSet Nothing <*> arbitrary
164
      "OP_CLUSTER_VERIFY_DISKS" -> pure OpCodes.OpClusterVerifyDisks
165
      "OP_GROUP_VERIFY_DISKS" ->
166
        OpCodes.OpGroupVerifyDisks <$> genNameNE
167
      "OP_CLUSTER_REPAIR_DISK_SIZES" ->
168
        OpCodes.OpClusterRepairDiskSizes <$> genNodeNamesNE
169
      "OP_CLUSTER_CONFIG_QUERY" ->
170
        OpCodes.OpClusterConfigQuery <$> genFieldsNE
171
      "OP_CLUSTER_RENAME" ->
172
        OpCodes.OpClusterRename <$> genNameNE
173
      "OP_CLUSTER_SET_PARAMS" ->
174
        OpCodes.OpClusterSetParams
175
          <$> arbitrary                    -- force
176
          <*> emptyMUD                     -- hv_state
177
          <*> emptyMUD                     -- disk_state
178
          <*> arbitrary                    -- vg_name
179
          <*> genMaybe arbitrary           -- enabled_hypervisors
180
          <*> genMaybe genEmptyContainer   -- hvparams
181
          <*> emptyMUD                     -- beparams
182
          <*> genMaybe genEmptyContainer   -- os_hvp
183
          <*> genMaybe genEmptyContainer   -- osparams
184
          <*> genMaybe genEmptyContainer   -- osparams_private_cluster
185
          <*> genMaybe genEmptyContainer   -- diskparams
186
          <*> genMaybe arbitrary           -- candidate_pool_size
187
          <*> genMaybe arbitrary           -- max_running_jobs
188
          <*> arbitrary                    -- uid_pool
189
          <*> arbitrary                    -- add_uids
190
          <*> arbitrary                    -- remove_uids
191
          <*> arbitrary                    -- maintain_node_health
192
          <*> arbitrary                    -- prealloc_wipe_disks
193
          <*> arbitrary                    -- nicparams
194
          <*> emptyMUD                     -- ndparams
195
          <*> emptyMUD                     -- ipolicy
196
          <*> arbitrary                    -- drbd_helper
197
          <*> arbitrary                    -- default_iallocator
198
          <*> emptyMUD                     -- default_iallocator_params
199
          <*> arbitrary                    -- master_netdev
200
          <*> arbitrary                    -- master_netmask
201
          <*> arbitrary                    -- reserved_lvs
202
          <*> arbitrary                    -- hidden_os
203
          <*> arbitrary                    -- blacklisted_os
204
          <*> arbitrary                    -- use_external_mip_script
205
          <*> arbitrary                    -- enabled_disk_templates
206
          <*> arbitrary                    -- modify_etc_hosts
207
          <*> genMaybe genName             -- file_storage_dir
208
          <*> genMaybe genName             -- shared_file_storage_dir
209
          <*> genMaybe genName             -- gluster_file_storage_dir
210
      "OP_CLUSTER_REDIST_CONF" -> pure OpCodes.OpClusterRedistConf
211
      "OP_CLUSTER_ACTIVATE_MASTER_IP" ->
212
        pure OpCodes.OpClusterActivateMasterIp
213
      "OP_CLUSTER_DEACTIVATE_MASTER_IP" ->
214
        pure OpCodes.OpClusterDeactivateMasterIp
215
      "OP_QUERY" ->
216
        OpCodes.OpQuery <$> arbitrary <*> arbitrary <*> arbitrary <*>
217
        pure Nothing
218
      "OP_QUERY_FIELDS" ->
219
        OpCodes.OpQueryFields <$> arbitrary <*> arbitrary
220
      "OP_OOB_COMMAND" ->
221
        OpCodes.OpOobCommand <$> genNodeNamesNE <*> return Nothing <*>
222
          arbitrary <*> arbitrary <*> arbitrary <*>
223
          (arbitrary `suchThat` (>0))
224
      "OP_NODE_REMOVE" ->
225
        OpCodes.OpNodeRemove <$> genNodeNameNE <*> return Nothing
226
      "OP_NODE_ADD" ->
227
        OpCodes.OpNodeAdd <$> genNodeNameNE <*> emptyMUD <*> emptyMUD <*>
228
          genMaybe genNameNE <*> genMaybe genNameNE <*> arbitrary <*>
229
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> emptyMUD
230
      "OP_NODE_QUERYVOLS" ->
231
        OpCodes.OpNodeQueryvols <$> arbitrary <*> genNodeNamesNE
232
      "OP_NODE_QUERY_STORAGE" ->
233
        OpCodes.OpNodeQueryStorage <$> arbitrary <*> arbitrary <*>
234
          genNodeNamesNE <*> genMaybe genNameNE
235
      "OP_NODE_MODIFY_STORAGE" ->
236
        OpCodes.OpNodeModifyStorage <$> genNodeNameNE <*> return Nothing <*>
237
          arbitrary <*> genMaybe genNameNE <*> pure emptyJSObject
238
      "OP_REPAIR_NODE_STORAGE" ->
239
        OpCodes.OpRepairNodeStorage <$> genNodeNameNE <*> return Nothing <*>
240
          arbitrary <*> genMaybe genNameNE <*> arbitrary
241
      "OP_NODE_SET_PARAMS" ->
242
        OpCodes.OpNodeSetParams <$> genNodeNameNE <*> return Nothing <*>
243
          arbitrary <*> emptyMUD <*> emptyMUD <*> arbitrary <*> arbitrary <*>
244
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
245
          genMaybe genNameNE <*> emptyMUD <*> arbitrary
246
      "OP_NODE_POWERCYCLE" ->
247
        OpCodes.OpNodePowercycle <$> genNodeNameNE <*> return Nothing <*>
248
          arbitrary
249
      "OP_NODE_MIGRATE" ->
250
        OpCodes.OpNodeMigrate <$> genNodeNameNE <*> return Nothing <*>
251
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
252
          return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
253
      "OP_NODE_EVACUATE" ->
254
        OpCodes.OpNodeEvacuate <$> arbitrary <*> genNodeNameNE <*>
255
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
256
          genMaybe genNameNE <*> arbitrary
257
      "OP_INSTANCE_CREATE" ->
258
        OpCodes.OpInstanceCreate
259
          <$> genFQDN                         -- instance_name
260
          <*> arbitrary                       -- force_variant
261
          <*> arbitrary                       -- wait_for_sync
262
          <*> arbitrary                       -- name_check
263
          <*> arbitrary                       -- ignore_ipolicy
264
          <*> arbitrary                       -- opportunistic_locking
265
          <*> pure emptyJSObject              -- beparams
266
          <*> arbitrary                       -- disks
267
          <*> arbitrary                       -- disk_template
268
          <*> arbitrary                       -- file_driver
269
          <*> genMaybe genNameNE              -- file_storage_dir
270
          <*> pure emptyJSObject              -- hvparams
271
          <*> arbitrary                       -- hypervisor
272
          <*> genMaybe genNameNE              -- iallocator
273
          <*> arbitrary                       -- identify_defaults
274
          <*> arbitrary                       -- ip_check
275
          <*> arbitrary                       -- conflicts_check
276
          <*> arbitrary                       -- mode
277
          <*> arbitrary                       -- nics
278
          <*> arbitrary                       -- no_install
279
          <*> pure emptyJSObject              -- osparams
280
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_private
281
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_secret
282
          <*> genMaybe genNameNE              -- os_type
283
          <*> genMaybe genNodeNameNE          -- pnode
284
          <*> return Nothing                  -- pnode_uuid
285
          <*> genMaybe genNodeNameNE          -- snode
286
          <*> return Nothing                  -- snode_uuid
287
          <*> genMaybe (pure [])              -- source_handshake
288
          <*> genMaybe genNodeNameNE          -- source_instance_name
289
          <*> arbitrary                       -- source_shutdown_timeout
290
          <*> genMaybe genNodeNameNE          -- source_x509_ca
291
          <*> return Nothing                  -- src_node
292
          <*> genMaybe genNodeNameNE          -- src_node_uuid
293
          <*> genMaybe genNameNE              -- src_path
294
          <*> arbitrary                       -- compress
295
          <*> arbitrary                       -- start
296
          <*> (genTags >>= mapM mkNonEmpty)   -- tags
297
          <*> arbitrary                       -- instance_communication
298
      "OP_INSTANCE_MULTI_ALLOC" ->
299
        OpCodes.OpInstanceMultiAlloc <$> arbitrary <*> genMaybe genNameNE <*>
300
        pure []
301
      "OP_INSTANCE_REINSTALL" ->
302
        OpCodes.OpInstanceReinstall <$> genFQDN <*> return Nothing <*>
303
          arbitrary <*> genMaybe genNameNE <*> genMaybe (pure emptyJSObject)
304
      "OP_INSTANCE_REMOVE" ->
305
        OpCodes.OpInstanceRemove <$> genFQDN <*> return Nothing <*>
306
          arbitrary <*> arbitrary
307
      "OP_INSTANCE_RENAME" ->
308
        OpCodes.OpInstanceRename <$> genFQDN <*> return Nothing <*>
309
          genNodeNameNE <*> arbitrary <*> arbitrary
310
      "OP_INSTANCE_STARTUP" ->
311
        OpCodes.OpInstanceStartup <$> genFQDN <*> return Nothing <*>
312
          arbitrary <*> arbitrary <*> pure emptyJSObject <*>
313
          pure emptyJSObject <*> arbitrary <*> arbitrary
314
      "OP_INSTANCE_SHUTDOWN" ->
315
        OpCodes.OpInstanceShutdown <$> genFQDN <*> return Nothing <*>
316
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
317
      "OP_INSTANCE_REBOOT" ->
318
        OpCodes.OpInstanceReboot <$> genFQDN <*> return Nothing <*>
319
          arbitrary <*> arbitrary <*> arbitrary
320
      "OP_INSTANCE_MOVE" ->
321
        OpCodes.OpInstanceMove <$> genFQDN <*> return Nothing <*>
322
          arbitrary <*> arbitrary <*> genNodeNameNE <*> return Nothing <*>
323
          arbitrary <*> arbitrary
324
      "OP_INSTANCE_CONSOLE" -> OpCodes.OpInstanceConsole <$> genFQDN <*>
325
          return Nothing
326
      "OP_INSTANCE_ACTIVATE_DISKS" ->
327
        OpCodes.OpInstanceActivateDisks <$> genFQDN <*> return Nothing <*>
328
          arbitrary <*> arbitrary
329
      "OP_INSTANCE_DEACTIVATE_DISKS" ->
330
        OpCodes.OpInstanceDeactivateDisks <$> genFQDN <*> return Nothing <*>
331
          arbitrary
332
      "OP_INSTANCE_RECREATE_DISKS" ->
333
        OpCodes.OpInstanceRecreateDisks <$> genFQDN <*> return Nothing <*>
334
          arbitrary <*> genNodeNamesNE <*> return Nothing <*>
335
          genMaybe genNameNE
336
      "OP_INSTANCE_QUERY_DATA" ->
337
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
338
          genNodeNamesNE <*> arbitrary
339
      "OP_INSTANCE_SET_PARAMS" ->
340
        OpCodes.OpInstanceSetParams
341
          <$> genFQDN                         -- instance_name
342
          <*> return Nothing                  -- instance_uuid
343
          <*> arbitrary                       -- force
344
          <*> arbitrary                       -- force_variant
345
          <*> arbitrary                       -- ignore_ipolicy
346
          <*> arbitrary                       -- nics
347
          <*> arbitrary                       -- disks
348
          <*> pure emptyJSObject              -- beparams
349
          <*> arbitrary                       -- runtime_mem
350
          <*> pure emptyJSObject              -- hvparams
351
          <*> arbitrary                       -- disk_template
352
          <*> genMaybe genNodeNameNE          -- pnode
353
          <*> return Nothing                  -- pnode_uuid
354
          <*> genMaybe genNodeNameNE          -- remote_node
355
          <*> return Nothing                  -- remote_node_uuid
356
          <*> genMaybe genNameNE              -- os_name
357
          <*> pure emptyJSObject              -- osparams
358
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_private
359
          <*> arbitrary                       -- wait_for_sync
360
          <*> arbitrary                       -- offline
361
          <*> arbitrary                       -- conflicts_check
362
          <*> arbitrary                       -- hotplug
363
          <*> arbitrary                       -- hotplug_if_possible
364
      "OP_INSTANCE_GROW_DISK" ->
365
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> return Nothing <*>
366
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
367
      "OP_INSTANCE_CHANGE_GROUP" ->
368
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> return Nothing <*>
369
          arbitrary <*> genMaybe genNameNE <*>
370
          genMaybe (resize maxNodes (listOf genNameNE))
371
      "OP_GROUP_ADD" ->
372
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
373
          emptyMUD <*> genMaybe genEmptyContainer <*>
374
          emptyMUD <*> emptyMUD <*> emptyMUD
375
      "OP_GROUP_ASSIGN_NODES" ->
376
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
377
          genNodeNamesNE <*> return Nothing
378
      "OP_GROUP_SET_PARAMS" ->
379
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
380
          emptyMUD <*> genMaybe genEmptyContainer <*>
381
          emptyMUD <*> emptyMUD <*> emptyMUD
382
      "OP_GROUP_REMOVE" ->
383
        OpCodes.OpGroupRemove <$> genNameNE
384
      "OP_GROUP_RENAME" ->
385
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
386
      "OP_GROUP_EVACUATE" ->
387
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
388
          genMaybe genNameNE <*> genMaybe genNamesNE
389
      "OP_OS_DIAGNOSE" ->
390
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
391
      "OP_EXT_STORAGE_DIAGNOSE" ->
392
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
393
      "OP_BACKUP_PREPARE" ->
394
        OpCodes.OpBackupPrepare <$> genFQDN <*> return Nothing <*> arbitrary
395
      "OP_BACKUP_EXPORT" ->
396
        OpCodes.OpBackupExport <$> genFQDN <*> return Nothing <*>
397
          arbitrary <*> arbitrary <*> arbitrary <*> return Nothing <*>
398
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
399
          genMaybe (pure []) <*> genMaybe genNameNE
400
      "OP_BACKUP_REMOVE" ->
401
        OpCodes.OpBackupRemove <$> genFQDN <*> return Nothing
402
      "OP_TEST_ALLOCATOR" ->
403
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
404
          genNameNE <*> genMaybe (pure []) <*> genMaybe (pure []) <*>
405
          arbitrary <*> genMaybe genNameNE <*>
406
          (genTags >>= mapM mkNonEmpty) <*>
407
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
408
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
409
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
410
      "OP_TEST_JQUEUE" ->
411
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
412
          resize 20 (listOf genFQDN) <*> arbitrary
413
      "OP_TEST_DUMMY" ->
414
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
415
          pure J.JSNull <*> pure J.JSNull
416
      "OP_NETWORK_ADD" ->
417
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIPv4Network <*>
418
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
419
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
420
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
421
      "OP_NETWORK_REMOVE" ->
422
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
423
      "OP_NETWORK_SET_PARAMS" ->
424
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
425
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
426
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
427
          genMaybe (listOf genIPv4Address)
428
      "OP_NETWORK_CONNECT" ->
429
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
430
          arbitrary <*> genNameNE <*> arbitrary
431
      "OP_NETWORK_DISCONNECT" ->
432
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
433
      "OP_RESTRICTED_COMMAND" ->
434
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
435
          return Nothing <*> genNameNE
436
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
437

    
438
-- | Generates one element of a reason trail
439
genReasonElem :: Gen ReasonElem
440
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
441

    
442
-- | Generates a reason trail
443
genReasonTrail :: Gen ReasonTrail
444
genReasonTrail = do
445
  size <- choose (0, 10)
446
  vectorOf size genReasonElem
447

    
448
instance Arbitrary OpCodes.CommonOpParams where
449
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
450
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
451
                genReasonTrail
452

    
453
-- * Helper functions
454

    
455
-- | Empty JSObject.
456
emptyJSObject :: J.JSObject J.JSValue
457
emptyJSObject = J.toJSObject []
458

    
459
-- | Empty maybe unchecked dictionary.
460
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
461
emptyMUD = genMaybe $ pure emptyJSObject
462

    
463
-- | Generates an empty container.
464
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
465
genEmptyContainer = pure . GenericContainer $ Map.fromList []
466

    
467
-- | Generates list of disk indices.
468
genDiskIndices :: Gen [DiskIndex]
469
genDiskIndices = do
470
  cnt <- choose (0, C.maxDisks)
471
  genUniquesList cnt arbitrary
472

    
473
-- | Generates a list of node names.
474
genNodeNames :: Gen [String]
475
genNodeNames = resize maxNodes (listOf genFQDN)
476

    
477
-- | Generates a list of node names in non-empty string type.
478
genNodeNamesNE :: Gen [NonEmptyString]
479
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
480

    
481
-- | Gets a node name in non-empty type.
482
genNodeNameNE :: Gen NonEmptyString
483
genNodeNameNE = genFQDN >>= mkNonEmpty
484

    
485
-- | Gets a name (non-fqdn) in non-empty type.
486
genNameNE :: Gen NonEmptyString
487
genNameNE = genName >>= mkNonEmpty
488

    
489
-- | Gets a list of names (non-fqdn) in non-empty type.
490
genNamesNE :: Gen [NonEmptyString]
491
genNamesNE = resize maxNodes (listOf genNameNE)
492

    
493
-- | Returns a list of non-empty fields.
494
genFieldsNE :: Gen [NonEmptyString]
495
genFieldsNE = genFields >>= mapM mkNonEmpty
496

    
497
-- | Generate a 3-byte MAC prefix.
498
genMacPrefix :: Gen NonEmptyString
499
genMacPrefix = do
500
  octets <- vectorOf 3 $ choose (0::Int, 255)
501
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
502

    
503
-- | JSObject of arbitrary data.
504
--
505
-- Since JSValue does not implement Arbitrary, I'll simply generate
506
-- (String, String) objects.
507
arbitraryPrivateJSObj :: Gen (J.JSObject (Private J.JSValue))
508
arbitraryPrivateJSObj =
509
  constructor <$> (fromNonEmpty <$> genNameNE)
510
              <*> (fromNonEmpty <$> genNameNE)
511
    where constructor k v = showPrivateJSObject [(k, v)]
512

    
513
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
514
$(genArbitrary ''OpCodes.MetaOpCode)
515

    
516
-- | Small helper to check for a failed JSON deserialisation
517
isJsonError :: J.Result a -> Bool
518
isJsonError (J.Error _) = True
519
isJsonError _           = False
520

    
521
-- * Test cases
522

    
523
-- | Check that opcode serialization is idempotent.
524
prop_serialization :: OpCodes.OpCode -> Property
525
prop_serialization = testSerialisation
526

    
527
-- | Check that Python and Haskell defined the same opcode list.
528
case_AllDefined :: HUnit.Assertion
529
case_AllDefined = do
530
  py_stdout <-
531
     runPython "from ganeti import opcodes\n\
532
               \from ganeti import serializer\n\
533
               \import sys\n\
534
               \print serializer.Dump([opid for opid in opcodes.OP_MAPPING])\n"
535
               ""
536
     >>= checkPythonResult
537
  py_ops <- case J.decode py_stdout::J.Result [String] of
538
               J.Ok ops -> return ops
539
               J.Error msg ->
540
                 HUnit.assertFailure ("Unable to decode opcode names: " ++ msg)
541
                 -- this already raised an expection, but we need it
542
                 -- for proper types
543
                 >> fail "Unable to decode opcode names"
544
  let hs_ops = sort OpCodes.allOpIDs
545
      extra_py = py_ops \\ hs_ops
546
      extra_hs = hs_ops \\ py_ops
547
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
548
                    unlines extra_py) (null extra_py)
549
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
550
                    unlines extra_hs) (null extra_hs)
551

    
552
-- | Custom HUnit test case that forks a Python process and checks
553
-- correspondence between Haskell-generated OpCodes and their Python
554
-- decoded, validated and re-encoded version.
555
--
556
-- Note that we have a strange beast here: since launching Python is
557
-- expensive, we don't do this via a usual QuickProperty, since that's
558
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
559
-- single HUnit assertion, and in it we manually use QuickCheck to
560
-- generate 500 opcodes times the number of defined opcodes, which
561
-- then we pass in bulk to Python. The drawbacks to this method are
562
-- two fold: we cannot control the number of generated opcodes, since
563
-- HUnit assertions don't get access to the test options, and for the
564
-- same reason we can't run a repeatable seed. We should probably find
565
-- a better way to do this, for example by having a
566
-- separately-launched Python process (if not running the tests would
567
-- be skipped).
568
case_py_compat_types :: HUnit.Assertion
569
case_py_compat_types = do
570
  let num_opcodes = length OpCodes.allOpIDs * 100
571
  opcodes <- genSample (vectorOf num_opcodes
572
                                   (arbitrary::Gen OpCodes.MetaOpCode))
573
  let with_sum = map (\o -> (OpCodes.opSummary $
574
                             OpCodes.metaOpCode o, o)) opcodes
575
      serialized = J.encode opcodes
576
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
577
  mapM_ (\op -> when (any (not . isAscii) (J.encode op)) .
578
                HUnit.assertFailure $
579
                  "OpCode has non-ASCII fields: " ++ show op
580
        ) opcodes
581
  py_stdout <-
582
     runPython "from ganeti import opcodes\n\
583
               \from ganeti import serializer\n\
584
               \import sys\n\
585
               \op_data = serializer.Load(sys.stdin.read())\n\
586
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
587
               \for op in decoded:\n\
588
               \  op.Validate(True)\n\
589
               \encoded = [(op.Summary(), op.__getstate__())\n\
590
               \           for op in decoded]\n\
591
               \print serializer.Dump(\
592
               \  encoded,\
593
               \  private_encoder=serializer.EncodeWithPrivateFields)"
594
               serialized
595
     >>= checkPythonResult
596
  let deserialised =
597
        J.decode py_stdout::J.Result [(String, OpCodes.MetaOpCode)]
598
  decoded <- case deserialised of
599
               J.Ok ops -> return ops
600
               J.Error msg ->
601
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
602
                 -- this already raised an expection, but we need it
603
                 -- for proper types
604
                 >> fail "Unable to decode opcodes"
605
  HUnit.assertEqual "Mismatch in number of returned opcodes"
606
    (length decoded) (length with_sum)
607
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
608
        ) $ zip with_sum decoded
609

    
610
-- | Custom HUnit test case that forks a Python process and checks
611
-- correspondence between Haskell OpCodes fields and their Python
612
-- equivalent.
613
case_py_compat_fields :: HUnit.Assertion
614
case_py_compat_fields = do
615
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
616
                         OpCodes.allOpIDs
617
  py_stdout <-
618
     runPython "from ganeti import opcodes\n\
619
               \import sys\n\
620
               \from ganeti import serializer\n\
621
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
622
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
623
               \print serializer.Dump(fields)" ""
624
     >>= checkPythonResult
625
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
626
  py_fields <- case deserialised of
627
                 J.Ok v -> return $ sort v
628
                 J.Error msg ->
629
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
630
                   -- this already raised an expection, but we need it
631
                   -- for proper types
632
                   >> fail "Unable to decode op fields"
633
  HUnit.assertEqual "Mismatch in number of returned opcodes"
634
    (length hs_fields) (length py_fields)
635
  HUnit.assertEqual "Mismatch in defined OP_IDs"
636
    (map fst hs_fields) (map fst py_fields)
637
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
638
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
639
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
640
             py_flds hs_flds
641
        ) $ zip hs_fields py_fields
642

    
643
-- | Checks that setOpComment works correctly.
644
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
645
prop_setOpComment op comment =
646
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
647
  in OpCodes.opComment common ==? Just comment
648

    
649
-- | Tests wrong (negative) disk index.
650
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
651
prop_mkDiskIndex_fail (Positive i) =
652
  case mkDiskIndex (negate i) of
653
    Bad msg -> printTestCase "error message " $
654
               "Invalid value" `isPrefixOf` msg
655
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
656
                       "' from negative value " ++ show (negate i)
657

    
658
-- | Tests a few invalid 'readRecreateDisks' cases.
659
case_readRecreateDisks_fail :: Assertion
660
case_readRecreateDisks_fail = do
661
  assertBool "null" $
662
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
663
  assertBool "string" $
664
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
665

    
666
-- | Tests a few invalid 'readDdmOldChanges' cases.
667
case_readDdmOldChanges_fail :: Assertion
668
case_readDdmOldChanges_fail = do
669
  assertBool "null" $
670
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
671
  assertBool "string" $
672
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
673

    
674
-- | Tests a few invalid 'readExportTarget' cases.
675
case_readExportTarget_fail :: Assertion
676
case_readExportTarget_fail = do
677
  assertBool "null" $
678
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
679
  assertBool "int" $
680
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
681

    
682
testSuite "OpCodes"
683
            [ 'prop_serialization
684
            , 'case_AllDefined
685
            , 'case_py_compat_types
686
            , 'case_py_compat_fields
687
            , 'prop_setOpComment
688
            , 'prop_mkDiskIndex_fail
689
            , 'case_readRecreateDisks_fail
690
            , 'case_readDdmOldChanges_fail
691
            , 'case_readExportTarget_fail
692
            ]