Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ 5b11f8db

History | View | Annotate | Download (5.4 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 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
{-# ANN module "HLint: ignore Use camelCase" #-}
48

    
49
-- * Arbitrary instances
50

    
51
$(genArbitrary ''OpCodes.ReplaceDisksMode)
52

    
53
instance Arbitrary OpCodes.DiskIndex where
54
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
55

    
56
instance Arbitrary OpCodes.OpCode where
57
  arbitrary = do
58
    op_id <- elements OpCodes.allOpIDs
59
    case op_id of
60
      "OP_TEST_DELAY" ->
61
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
62
                 <*> resize maxNodes (listOf getFQDN)
63
      "OP_INSTANCE_REPLACE_DISKS" ->
64
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
65
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
66
      "OP_INSTANCE_FAILOVER" ->
67
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
68
          getMaybe getFQDN
69
      "OP_INSTANCE_MIGRATE" ->
70
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
71
          arbitrary <*> arbitrary <*> getMaybe getFQDN
72
      _ -> fail "Wrong opcode"
73

    
74
-- * Test cases
75

    
76
-- | Check that opcode serialization is idempotent.
77
prop_serialization :: OpCodes.OpCode -> Property
78
prop_serialization = testSerialisation
79

    
80
-- | Check that Python and Haskell defined the same opcode list.
81
case_AllDefined :: HUnit.Assertion
82
case_AllDefined = do
83
  py_stdout <- runPython "from ganeti import opcodes\n\
84
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
85
               checkPythonResult
86
  let py_ops = sort $ lines py_stdout
87
      hs_ops = OpCodes.allOpIDs
88
      -- extra_py = py_ops \\ hs_ops
89
      extra_hs = hs_ops \\ py_ops
90
  -- FIXME: uncomment when we have parity
91
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
92
  --                  unlines extra_py) (null extra_py)
93
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
94
                    unlines extra_hs) (null extra_hs)
95

    
96
-- | Custom HUnit test case that forks a Python process and checks
97
-- correspondence between Haskell-generated OpCodes and their Python
98
-- decoded, validated and re-encoded version.
99
--
100
-- Note that we have a strange beast here: since launching Python is
101
-- expensive, we don't do this via a usual QuickProperty, since that's
102
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
103
-- single HUnit assertion, and in it we manually use QuickCheck to
104
-- generate 500 opcodes times the number of defined opcodes, which
105
-- then we pass in bulk to Python. The drawbacks to this method are
106
-- two fold: we cannot control the number of generated opcodes, since
107
-- HUnit assertions don't get access to the test options, and for the
108
-- same reason we can't run a repeatable seed. We should probably find
109
-- a better way to do this, for example by having a
110
-- separately-launched Python process (if not running the tests would
111
-- be skipped).
112
case_py_compat :: HUnit.Assertion
113
case_py_compat = do
114
  let num_opcodes = length OpCodes.allOpIDs * 500
115
  sample_opcodes <- sample' (vectorOf num_opcodes
116
                             (arbitrary::Gen OpCodes.OpCode))
117
  let opcodes = head sample_opcodes
118
      serialized = J.encode opcodes
119
  py_stdout <-
120
     runPython "from ganeti import opcodes\n\
121
               \import sys\n\
122
               \from ganeti import serializer\n\
123
               \op_data = serializer.Load(sys.stdin.read())\n\
124
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
125
               \for op in decoded:\n\
126
               \  op.Validate(True)\n\
127
               \encoded = [op.__getstate__() for op in decoded]\n\
128
               \print serializer.Dump(encoded)" serialized
129
     >>= checkPythonResult
130
  let deserialised = J.decode py_stdout::J.Result [OpCodes.OpCode]
131
  decoded <- case deserialised of
132
               J.Ok ops -> return ops
133
               J.Error msg ->
134
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
135
                 -- this already raised an expection, but we need it
136
                 -- for proper types
137
                 >> fail "Unable to decode opcodes"
138
  HUnit.assertEqual "Mismatch in number of returned opcodes"
139
    (length opcodes) (length decoded)
140
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
141
        ) $ zip opcodes decoded
142

    
143
testSuite "OpCodes"
144
            [ 'prop_serialization
145
            , 'case_AllDefined
146
            , 'case_py_compat
147
            ]