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