Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ 1493a93b

History | View | Annotate | Download (5.5 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 aed2325f Iustin Pop
-- * Arbitrary instances
48 aed2325f Iustin Pop
49 aed2325f Iustin Pop
instance Arbitrary OpCodes.ReplaceDisksMode where
50 aed2325f Iustin Pop
  arbitrary = elements [minBound..maxBound]
51 aed2325f Iustin Pop
52 aed2325f Iustin Pop
instance Arbitrary OpCodes.DiskIndex where
53 aed2325f Iustin Pop
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
54 aed2325f Iustin Pop
55 aed2325f Iustin Pop
instance Arbitrary OpCodes.OpCode where
56 aed2325f Iustin Pop
  arbitrary = do
57 aed2325f Iustin Pop
    op_id <- elements OpCodes.allOpIDs
58 aed2325f Iustin Pop
    case op_id of
59 aed2325f Iustin Pop
      "OP_TEST_DELAY" ->
60 aed2325f Iustin Pop
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
61 aed2325f Iustin Pop
                 <*> resize maxNodes (listOf getFQDN)
62 aed2325f Iustin Pop
      "OP_INSTANCE_REPLACE_DISKS" ->
63 aed2325f Iustin Pop
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
64 aed2325f Iustin Pop
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
65 aed2325f Iustin Pop
      "OP_INSTANCE_FAILOVER" ->
66 aed2325f Iustin Pop
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
67 aed2325f Iustin Pop
          getMaybe getFQDN
68 aed2325f Iustin Pop
      "OP_INSTANCE_MIGRATE" ->
69 aed2325f Iustin Pop
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
70 aed2325f Iustin Pop
          arbitrary <*> arbitrary <*> getMaybe getFQDN
71 aed2325f Iustin Pop
      _ -> fail "Wrong opcode"
72 aed2325f Iustin Pop
73 aed2325f Iustin Pop
-- * Test cases
74 aed2325f Iustin Pop
75 aed2325f Iustin Pop
-- | Check that opcode serialization is idempotent.
76 20bc5360 Iustin Pop
prop_serialization :: OpCodes.OpCode -> Property
77 20bc5360 Iustin Pop
prop_serialization op =
78 aed2325f Iustin Pop
  case J.readJSON (J.showJSON op) of
79 aed2325f Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
80 aed2325f Iustin Pop
    J.Ok op' -> op ==? op'
81 aed2325f Iustin Pop
82 aed2325f Iustin Pop
-- | Check that Python and Haskell defined the same opcode list.
83 20bc5360 Iustin Pop
case_AllDefined :: HUnit.Assertion
84 20bc5360 Iustin Pop
case_AllDefined = do
85 aed2325f Iustin Pop
  py_stdout <- runPython "from ganeti import opcodes\n\
86 aed2325f Iustin Pop
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
87 aed2325f Iustin Pop
               checkPythonResult
88 aed2325f Iustin Pop
  let py_ops = sort $ lines py_stdout
89 aed2325f Iustin Pop
      hs_ops = OpCodes.allOpIDs
90 aed2325f Iustin Pop
      -- extra_py = py_ops \\ hs_ops
91 aed2325f Iustin Pop
      extra_hs = hs_ops \\ py_ops
92 aed2325f Iustin Pop
  -- FIXME: uncomment when we have parity
93 aed2325f Iustin Pop
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
94 aed2325f Iustin Pop
  --                  unlines extra_py) (null extra_py)
95 aed2325f Iustin Pop
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
96 aed2325f Iustin Pop
                    unlines extra_hs) (null extra_hs)
97 aed2325f Iustin Pop
98 aed2325f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
99 aed2325f Iustin Pop
-- correspondence between Haskell-generated OpCodes and their Python
100 aed2325f Iustin Pop
-- decoded, validated and re-encoded version.
101 aed2325f Iustin Pop
--
102 aed2325f Iustin Pop
-- Note that we have a strange beast here: since launching Python is
103 aed2325f Iustin Pop
-- expensive, we don't do this via a usual QuickProperty, since that's
104 aed2325f Iustin Pop
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
105 aed2325f Iustin Pop
-- single HUnit assertion, and in it we manually use QuickCheck to
106 aed2325f Iustin Pop
-- generate 500 opcodes times the number of defined opcodes, which
107 aed2325f Iustin Pop
-- then we pass in bulk to Python. The drawbacks to this method are
108 aed2325f Iustin Pop
-- two fold: we cannot control the number of generated opcodes, since
109 aed2325f Iustin Pop
-- HUnit assertions don't get access to the test options, and for the
110 aed2325f Iustin Pop
-- same reason we can't run a repeatable seed. We should probably find
111 aed2325f Iustin Pop
-- a better way to do this, for example by having a
112 aed2325f Iustin Pop
-- separately-launched Python process (if not running the tests would
113 aed2325f Iustin Pop
-- be skipped).
114 20bc5360 Iustin Pop
case_py_compat :: HUnit.Assertion
115 20bc5360 Iustin Pop
case_py_compat = do
116 aed2325f Iustin Pop
  let num_opcodes = length OpCodes.allOpIDs * 500
117 aed2325f Iustin Pop
  sample_opcodes <- sample' (vectorOf num_opcodes
118 aed2325f Iustin Pop
                             (arbitrary::Gen OpCodes.OpCode))
119 aed2325f Iustin Pop
  let opcodes = head sample_opcodes
120 aed2325f Iustin Pop
      serialized = J.encode opcodes
121 aed2325f Iustin Pop
  py_stdout <-
122 aed2325f Iustin Pop
     runPython "from ganeti import opcodes\n\
123 aed2325f Iustin Pop
               \import sys\n\
124 aed2325f Iustin Pop
               \from ganeti import serializer\n\
125 aed2325f Iustin Pop
               \op_data = serializer.Load(sys.stdin.read())\n\
126 aed2325f Iustin Pop
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
127 aed2325f Iustin Pop
               \for op in decoded:\n\
128 aed2325f Iustin Pop
               \  op.Validate(True)\n\
129 aed2325f Iustin Pop
               \encoded = [op.__getstate__() for op in decoded]\n\
130 aed2325f Iustin Pop
               \print serializer.Dump(encoded)" serialized
131 aed2325f Iustin Pop
     >>= checkPythonResult
132 aed2325f Iustin Pop
  let deserialised = (J.decode py_stdout::J.Result [OpCodes.OpCode])
133 aed2325f Iustin Pop
  decoded <- case deserialised of
134 aed2325f Iustin Pop
               J.Ok ops -> return ops
135 aed2325f Iustin Pop
               J.Error msg ->
136 aed2325f Iustin Pop
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
137 aed2325f Iustin Pop
                 -- this already raised an expection, but we need it
138 aed2325f Iustin Pop
                 -- for proper types
139 aed2325f Iustin Pop
                 >> fail "Unable to decode opcodes"
140 aed2325f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
141 aed2325f Iustin Pop
    (length opcodes) (length decoded)
142 aed2325f Iustin Pop
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
143 aed2325f Iustin Pop
        ) $ zip opcodes decoded
144 aed2325f Iustin Pop
145 aed2325f Iustin Pop
testSuite "OpCodes"
146 20bc5360 Iustin Pop
            [ 'prop_serialization
147 20bc5360 Iustin Pop
            , 'case_AllDefined
148 20bc5360 Iustin Pop
            , 'case_py_compat
149 aed2325f Iustin Pop
            ]