Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ 3bebda52

History | View | Annotate | Download (5.6 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.TagObject)
52

    
53
$(genArbitrary ''OpCodes.ReplaceDisksMode)
54

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

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

    
80
-- * Test cases
81

    
82
-- | Check that opcode serialization is idempotent.
83
prop_serialization :: OpCodes.OpCode -> Property
84
prop_serialization = testSerialisation
85

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

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

    
149
testSuite "OpCodes"
150
            [ 'prop_serialization
151
            , 'case_AllDefined
152
            , 'case_py_compat
153
            ]