Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ 61899e64

History | View | Annotate | Download (5.8 kB)

1 aed2325f Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aed2325f Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 aed2325f Iustin Pop
4 aed2325f Iustin Pop
{-| Unittests for ganeti-htools.
5 aed2325f Iustin Pop
6 aed2325f Iustin Pop
-}
7 aed2325f Iustin Pop
8 aed2325f Iustin Pop
{-
9 aed2325f Iustin Pop
10 aed2325f Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 aed2325f Iustin Pop
12 aed2325f Iustin Pop
This program is free software; you can redistribute it and/or modify
13 aed2325f Iustin Pop
it under the terms of the GNU General Public License as published by
14 aed2325f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 aed2325f Iustin Pop
(at your option) any later version.
16 aed2325f Iustin Pop
17 aed2325f Iustin Pop
This program is distributed in the hope that it will be useful, but
18 aed2325f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 aed2325f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 aed2325f Iustin Pop
General Public License for more details.
21 aed2325f Iustin Pop
22 aed2325f Iustin Pop
You should have received a copy of the GNU General Public License
23 aed2325f Iustin Pop
along with this program; if not, write to the Free Software
24 aed2325f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 aed2325f Iustin Pop
02110-1301, USA.
26 aed2325f Iustin Pop
27 aed2325f Iustin Pop
-}
28 aed2325f Iustin Pop
29 aed2325f Iustin Pop
module Test.Ganeti.OpCodes
30 aed2325f Iustin Pop
  ( testOpCodes
31 aed2325f Iustin Pop
  , OpCodes.OpCode(..)
32 aed2325f Iustin Pop
  ) where
33 aed2325f Iustin Pop
34 aed2325f Iustin Pop
import qualified Test.HUnit as HUnit
35 aed2325f Iustin Pop
import Test.QuickCheck
36 aed2325f Iustin Pop
37 aed2325f Iustin Pop
import Control.Applicative
38 aed2325f Iustin Pop
import Data.List
39 aed2325f Iustin Pop
import qualified Text.JSON as J
40 aed2325f Iustin Pop
41 aed2325f Iustin Pop
import Test.Ganeti.TestHelper
42 aed2325f Iustin Pop
import Test.Ganeti.TestCommon
43 aed2325f Iustin Pop
44 aed2325f Iustin Pop
import qualified Ganeti.Constants as C
45 aed2325f Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
46 aed2325f Iustin Pop
47 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
48 5b11f8db Iustin Pop
49 aed2325f Iustin Pop
-- * Arbitrary instances
50 aed2325f Iustin Pop
51 d8e7c45e Iustin Pop
instance Arbitrary OpCodes.TagObject where
52 d8e7c45e Iustin Pop
  arbitrary = oneof [ OpCodes.TagInstance <$> getFQDN
53 d8e7c45e Iustin Pop
                    , OpCodes.TagNode     <$> getFQDN
54 d8e7c45e Iustin Pop
                    , OpCodes.TagGroup    <$> getFQDN
55 d8e7c45e Iustin Pop
                    , pure OpCodes.TagCluster
56 d8e7c45e Iustin Pop
                    ]
57 367c4241 Dato Simó
58 7022db83 Iustin Pop
$(genArbitrary ''OpCodes.ReplaceDisksMode)
59 aed2325f Iustin Pop
60 aed2325f Iustin Pop
instance Arbitrary OpCodes.DiskIndex where
61 aed2325f Iustin Pop
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
62 aed2325f Iustin Pop
63 aed2325f Iustin Pop
instance Arbitrary OpCodes.OpCode where
64 aed2325f Iustin Pop
  arbitrary = do
65 aed2325f Iustin Pop
    op_id <- elements OpCodes.allOpIDs
66 aed2325f Iustin Pop
    case op_id of
67 aed2325f Iustin Pop
      "OP_TEST_DELAY" ->
68 aed2325f Iustin Pop
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
69 aed2325f Iustin Pop
                 <*> resize maxNodes (listOf getFQDN)
70 aed2325f Iustin Pop
      "OP_INSTANCE_REPLACE_DISKS" ->
71 aed2325f Iustin Pop
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
72 aed2325f Iustin Pop
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
73 aed2325f Iustin Pop
      "OP_INSTANCE_FAILOVER" ->
74 aed2325f Iustin Pop
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
75 aed2325f Iustin Pop
          getMaybe getFQDN
76 aed2325f Iustin Pop
      "OP_INSTANCE_MIGRATE" ->
77 aed2325f Iustin Pop
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
78 aed2325f Iustin Pop
          arbitrary <*> arbitrary <*> getMaybe getFQDN
79 3bebda52 Dato Simó
      "OP_TAGS_SET" ->
80 d8e7c45e Iustin Pop
        OpCodes.OpTagsSet <$> arbitrary <*> genTags
81 3bebda52 Dato Simó
      "OP_TAGS_DEL" ->
82 d8e7c45e Iustin Pop
        OpCodes.OpTagsSet <$> arbitrary <*> genTags
83 aed2325f Iustin Pop
      _ -> fail "Wrong opcode"
84 aed2325f Iustin Pop
85 aed2325f Iustin Pop
-- * Test cases
86 aed2325f Iustin Pop
87 aed2325f Iustin Pop
-- | Check that opcode serialization is idempotent.
88 20bc5360 Iustin Pop
prop_serialization :: OpCodes.OpCode -> Property
89 63b068c1 Iustin Pop
prop_serialization = testSerialisation
90 aed2325f Iustin Pop
91 aed2325f Iustin Pop
-- | Check that Python and Haskell defined the same opcode list.
92 20bc5360 Iustin Pop
case_AllDefined :: HUnit.Assertion
93 20bc5360 Iustin Pop
case_AllDefined = do
94 aed2325f Iustin Pop
  py_stdout <- runPython "from ganeti import opcodes\n\
95 aed2325f Iustin Pop
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
96 aed2325f Iustin Pop
               checkPythonResult
97 aed2325f Iustin Pop
  let py_ops = sort $ lines py_stdout
98 aed2325f Iustin Pop
      hs_ops = OpCodes.allOpIDs
99 aed2325f Iustin Pop
      -- extra_py = py_ops \\ hs_ops
100 aed2325f Iustin Pop
      extra_hs = hs_ops \\ py_ops
101 aed2325f Iustin Pop
  -- FIXME: uncomment when we have parity
102 aed2325f Iustin Pop
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
103 aed2325f Iustin Pop
  --                  unlines extra_py) (null extra_py)
104 aed2325f Iustin Pop
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
105 aed2325f Iustin Pop
                    unlines extra_hs) (null extra_hs)
106 aed2325f Iustin Pop
107 aed2325f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
108 aed2325f Iustin Pop
-- correspondence between Haskell-generated OpCodes and their Python
109 aed2325f Iustin Pop
-- decoded, validated and re-encoded version.
110 aed2325f Iustin Pop
--
111 aed2325f Iustin Pop
-- Note that we have a strange beast here: since launching Python is
112 aed2325f Iustin Pop
-- expensive, we don't do this via a usual QuickProperty, since that's
113 aed2325f Iustin Pop
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
114 aed2325f Iustin Pop
-- single HUnit assertion, and in it we manually use QuickCheck to
115 aed2325f Iustin Pop
-- generate 500 opcodes times the number of defined opcodes, which
116 aed2325f Iustin Pop
-- then we pass in bulk to Python. The drawbacks to this method are
117 aed2325f Iustin Pop
-- two fold: we cannot control the number of generated opcodes, since
118 aed2325f Iustin Pop
-- HUnit assertions don't get access to the test options, and for the
119 aed2325f Iustin Pop
-- same reason we can't run a repeatable seed. We should probably find
120 aed2325f Iustin Pop
-- a better way to do this, for example by having a
121 aed2325f Iustin Pop
-- separately-launched Python process (if not running the tests would
122 aed2325f Iustin Pop
-- be skipped).
123 20bc5360 Iustin Pop
case_py_compat :: HUnit.Assertion
124 20bc5360 Iustin Pop
case_py_compat = do
125 aed2325f Iustin Pop
  let num_opcodes = length OpCodes.allOpIDs * 500
126 aed2325f Iustin Pop
  sample_opcodes <- sample' (vectorOf num_opcodes
127 aed2325f Iustin Pop
                             (arbitrary::Gen OpCodes.OpCode))
128 aed2325f Iustin Pop
  let opcodes = head sample_opcodes
129 aed2325f Iustin Pop
      serialized = J.encode opcodes
130 aed2325f Iustin Pop
  py_stdout <-
131 aed2325f Iustin Pop
     runPython "from ganeti import opcodes\n\
132 aed2325f Iustin Pop
               \import sys\n\
133 aed2325f Iustin Pop
               \from ganeti import serializer\n\
134 aed2325f Iustin Pop
               \op_data = serializer.Load(sys.stdin.read())\n\
135 aed2325f Iustin Pop
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
136 aed2325f Iustin Pop
               \for op in decoded:\n\
137 aed2325f Iustin Pop
               \  op.Validate(True)\n\
138 aed2325f Iustin Pop
               \encoded = [op.__getstate__() for op in decoded]\n\
139 aed2325f Iustin Pop
               \print serializer.Dump(encoded)" serialized
140 aed2325f Iustin Pop
     >>= checkPythonResult
141 5b11f8db Iustin Pop
  let deserialised = J.decode py_stdout::J.Result [OpCodes.OpCode]
142 aed2325f Iustin Pop
  decoded <- case deserialised of
143 aed2325f Iustin Pop
               J.Ok ops -> return ops
144 aed2325f Iustin Pop
               J.Error msg ->
145 aed2325f Iustin Pop
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
146 aed2325f Iustin Pop
                 -- this already raised an expection, but we need it
147 aed2325f Iustin Pop
                 -- for proper types
148 aed2325f Iustin Pop
                 >> fail "Unable to decode opcodes"
149 aed2325f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
150 aed2325f Iustin Pop
    (length opcodes) (length decoded)
151 aed2325f Iustin Pop
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
152 aed2325f Iustin Pop
        ) $ zip opcodes decoded
153 aed2325f Iustin Pop
154 aed2325f Iustin Pop
testSuite "OpCodes"
155 20bc5360 Iustin Pop
            [ 'prop_serialization
156 20bc5360 Iustin Pop
            , 'case_AllDefined
157 20bc5360 Iustin Pop
            , 'case_py_compat
158 aed2325f Iustin Pop
            ]