Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ 61899e64

History | View | Annotate | Download (5.8 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
instance Arbitrary OpCodes.TagObject where
52
  arbitrary = oneof [ OpCodes.TagInstance <$> getFQDN
53
                    , OpCodes.TagNode     <$> getFQDN
54
                    , OpCodes.TagGroup    <$> getFQDN
55
                    , pure OpCodes.TagCluster
56
                    ]
57

    
58
$(genArbitrary ''OpCodes.ReplaceDisksMode)
59

    
60
instance Arbitrary OpCodes.DiskIndex where
61
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
62

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

    
85
-- * Test cases
86

    
87
-- | Check that opcode serialization is idempotent.
88
prop_serialization :: OpCodes.OpCode -> Property
89
prop_serialization = testSerialisation
90

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

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

    
154
testSuite "OpCodes"
155
            [ 'prop_serialization
156
            , 'case_AllDefined
157
            , 'case_py_compat
158
            ]