Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ a3f02317

History | View | Annotate | Download (17.7 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 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 qualified Test.HUnit as HUnit
35
import Test.QuickCheck
36

    
37
import Control.Applicative
38
import Data.List
39
import qualified Data.Map as Map
40
import qualified Text.JSON as J
41

    
42
import Test.Ganeti.TestHelper
43
import Test.Ganeti.TestCommon
44
import Test.Ganeti.Types ()
45
import Test.Ganeti.Query.Language
46

    
47
import qualified Ganeti.Constants as C
48
import qualified Ganeti.OpCodes as OpCodes
49
import Ganeti.Types
50
import Ganeti.OpParams
51
import Ganeti.JSON
52

    
53
{-# ANN module "HLint: ignore Use camelCase" #-}
54

    
55
-- * Arbitrary instances
56

    
57
instance Arbitrary OpCodes.TagObject where
58
  arbitrary = oneof [ OpCodes.TagInstance <$> getFQDN
59
                    , OpCodes.TagNode     <$> getFQDN
60
                    , OpCodes.TagGroup    <$> getFQDN
61
                    , pure OpCodes.TagCluster
62
                    ]
63

    
64
$(genArbitrary ''OpCodes.ReplaceDisksMode)
65

    
66
$(genArbitrary ''DiskAccess)
67

    
68
instance Arbitrary OpCodes.DiskIndex where
69
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
70

    
71
instance Arbitrary INicParams where
72
  arbitrary = INicParams <$> getMaybe genNameNE <*> getMaybe getName <*>
73
              getMaybe genNameNE <*> getMaybe genNameNE
74

    
75
instance Arbitrary IDiskParams where
76
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
77
              getMaybe genNameNE <*> getMaybe genNameNE <*>
78
              getMaybe genNameNE
79

    
80
instance Arbitrary RecreateDisksInfo where
81
  arbitrary = oneof [ pure RecreateDisksAll
82
                    , RecreateDisksIndices <$> arbitrary
83
                    , RecreateDisksParams <$> arbitrary
84
                    ]
85

    
86
instance Arbitrary DdmOldChanges where
87
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
88
                    , DdmOldMod   <$> arbitrary
89
                    ]
90

    
91
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
92
  arbitrary = oneof [ pure SetParamsEmpty
93
                    , SetParamsDeprecated <$> arbitrary
94
                    , SetParamsNew        <$> arbitrary
95
                    ]
96

    
97
instance Arbitrary ExportTarget where
98
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
99
                    , ExportTargetRemote <$> pure []
100
                    ]
101

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

    
313
-- * Helper functions
314

    
315
-- | Empty JSObject.
316
emptyJSObject :: J.JSObject J.JSValue
317
emptyJSObject = J.toJSObject []
318

    
319
-- | Empty maybe unchecked dictionary.
320
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
321
emptyMUD = getMaybe $ pure emptyJSObject
322

    
323
-- | Generates an empty container.
324
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
325
genEmptyContainer = pure . GenericContainer $ Map.fromList []
326

    
327
-- | Generates list of disk indices.
328
genDiskIndices :: Gen [DiskIndex]
329
genDiskIndices = do
330
  cnt <- choose (0, C.maxDisks)
331
  genUniquesList cnt
332

    
333
-- | Generates a list of node names.
334
genNodeNames :: Gen [String]
335
genNodeNames = resize maxNodes (listOf getFQDN)
336

    
337
-- | Generates a list of node names in non-empty string type.
338
genNodeNamesNE :: Gen [NonEmptyString]
339
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
340

    
341
-- | Gets a node name in non-empty type.
342
genNodeNameNE :: Gen NonEmptyString
343
genNodeNameNE = getFQDN >>= mkNonEmpty
344

    
345
-- | Gets a name (non-fqdn) in non-empty type.
346
genNameNE :: Gen NonEmptyString
347
genNameNE = getName >>= mkNonEmpty
348

    
349
-- | Gets a list of names (non-fqdn) in non-empty type.
350
genNamesNE :: Gen [NonEmptyString]
351
genNamesNE = resize maxNodes (listOf genNameNE)
352

    
353
-- | Returns a list of non-empty fields.
354
genFieldsNE :: Gen [NonEmptyString]
355
genFieldsNE = getFields >>= mapM mkNonEmpty
356

    
357
-- * Test cases
358

    
359
-- | Check that opcode serialization is idempotent.
360
prop_serialization :: OpCodes.OpCode -> Property
361
prop_serialization = testSerialisation
362

    
363
-- | Check that Python and Haskell defined the same opcode list.
364
case_AllDefined :: HUnit.Assertion
365
case_AllDefined = do
366
  py_stdout <- runPython "from ganeti import opcodes\n\
367
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
368
               checkPythonResult
369
  let py_ops = sort $ lines py_stdout
370
      hs_ops = OpCodes.allOpIDs
371
      -- extra_py = py_ops \\ hs_ops
372
      extra_hs = hs_ops \\ py_ops
373
  -- FIXME: uncomment when we have parity
374
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
375
  --                  unlines extra_py) (null extra_py)
376
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
377
                    unlines extra_hs) (null extra_hs)
378

    
379
-- | Custom HUnit test case that forks a Python process and checks
380
-- correspondence between Haskell-generated OpCodes and their Python
381
-- decoded, validated and re-encoded version.
382
--
383
-- Note that we have a strange beast here: since launching Python is
384
-- expensive, we don't do this via a usual QuickProperty, since that's
385
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
386
-- single HUnit assertion, and in it we manually use QuickCheck to
387
-- generate 500 opcodes times the number of defined opcodes, which
388
-- then we pass in bulk to Python. The drawbacks to this method are
389
-- two fold: we cannot control the number of generated opcodes, since
390
-- HUnit assertions don't get access to the test options, and for the
391
-- same reason we can't run a repeatable seed. We should probably find
392
-- a better way to do this, for example by having a
393
-- separately-launched Python process (if not running the tests would
394
-- be skipped).
395
case_py_compat :: HUnit.Assertion
396
case_py_compat = do
397
  let num_opcodes = length OpCodes.allOpIDs * 500
398
  sample_opcodes <- sample' (vectorOf num_opcodes
399
                             (arbitrary::Gen OpCodes.OpCode))
400
  let opcodes = head sample_opcodes
401
      serialized = J.encode opcodes
402
  py_stdout <-
403
     runPython "from ganeti import opcodes\n\
404
               \import sys\n\
405
               \from ganeti import serializer\n\
406
               \op_data = serializer.Load(sys.stdin.read())\n\
407
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
408
               \for op in decoded:\n\
409
               \  op.Validate(True)\n\
410
               \encoded = [op.__getstate__() for op in decoded]\n\
411
               \print serializer.Dump(encoded)" serialized
412
     >>= checkPythonResult
413
  let deserialised = J.decode py_stdout::J.Result [OpCodes.OpCode]
414
  decoded <- case deserialised of
415
               J.Ok ops -> return ops
416
               J.Error msg ->
417
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
418
                 -- this already raised an expection, but we need it
419
                 -- for proper types
420
                 >> fail "Unable to decode opcodes"
421
  HUnit.assertEqual "Mismatch in number of returned opcodes"
422
    (length opcodes) (length decoded)
423
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
424
        ) $ zip opcodes decoded
425

    
426
testSuite "OpCodes"
427
            [ 'prop_serialization
428
            , 'case_AllDefined
429
            , 'case_py_compat
430
            ]