Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / OpCodes.hs @ c7d249d0

History | View | Annotate | Download (6.3 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
import Test.Ganeti.Types ()
44

    
45
import qualified Ganeti.Constants as C
46
import qualified Ganeti.OpCodes as OpCodes
47
import Ganeti.Types
48
import Ganeti.OpParams
49

    
50
{-# ANN module "HLint: ignore Use camelCase" #-}
51

    
52
-- * Arbitrary instances
53

    
54
instance Arbitrary OpCodes.TagObject where
55
  arbitrary = oneof [ OpCodes.TagInstance <$> getFQDN
56
                    , OpCodes.TagNode     <$> getFQDN
57
                    , OpCodes.TagGroup    <$> getFQDN
58
                    , pure OpCodes.TagCluster
59
                    ]
60

    
61
$(genArbitrary ''OpCodes.ReplaceDisksMode)
62

    
63
instance Arbitrary OpCodes.DiskIndex where
64
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
65

    
66
instance Arbitrary OpCodes.OpCode where
67
  arbitrary = do
68
    op_id <- elements OpCodes.allOpIDs
69
    case op_id of
70
      "OP_TEST_DELAY" ->
71
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
72
                 <*> genNodeNames
73
      "OP_INSTANCE_REPLACE_DISKS" ->
74
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*>
75
          getMaybe genNodeNameNE <*> arbitrary <*> genDiskIndices <*> arbitrary
76
      "OP_INSTANCE_FAILOVER" ->
77
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
78
          getMaybe genNodeNameNE
79
      "OP_INSTANCE_MIGRATE" ->
80
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
81
          arbitrary <*> arbitrary <*> getMaybe genNodeNameNE
82
      "OP_TAGS_SET" ->
83
        OpCodes.OpTagsSet <$> arbitrary <*> genTags
84
      "OP_TAGS_DEL" ->
85
        OpCodes.OpTagsSet <$> arbitrary <*> genTags
86
      _ -> fail "Wrong opcode"
87

    
88
-- * Helper functions
89

    
90
-- | Generates list of disk indices.
91
genDiskIndices :: Gen [DiskIndex]
92
genDiskIndices = do
93
  cnt <- choose (0, C.maxDisks)
94
  genUniquesList cnt
95

    
96
-- | Generates a list of node names.
97
genNodeNames :: Gen [String]
98
genNodeNames = resize maxNodes (listOf getFQDN)
99

    
100
-- | Gets a node name in non-empty type.
101
genNodeNameNE :: Gen NonEmptyString
102
genNodeNameNE = getFQDN >>= mkNonEmpty
103

    
104
-- * Test cases
105

    
106
-- | Check that opcode serialization is idempotent.
107
prop_serialization :: OpCodes.OpCode -> Property
108
prop_serialization = testSerialisation
109

    
110
-- | Check that Python and Haskell defined the same opcode list.
111
case_AllDefined :: HUnit.Assertion
112
case_AllDefined = do
113
  py_stdout <- runPython "from ganeti import opcodes\n\
114
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
115
               checkPythonResult
116
  let py_ops = sort $ lines py_stdout
117
      hs_ops = OpCodes.allOpIDs
118
      -- extra_py = py_ops \\ hs_ops
119
      extra_hs = hs_ops \\ py_ops
120
  -- FIXME: uncomment when we have parity
121
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
122
  --                  unlines extra_py) (null extra_py)
123
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
124
                    unlines extra_hs) (null extra_hs)
125

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

    
173
testSuite "OpCodes"
174
            [ 'prop_serialization
175
            , 'case_AllDefined
176
            , 'case_py_compat
177
            ]