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