Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 241cea1e

History | View | Annotate | Download (13.8 kB)

1 9924d61e Iustin Pop
{-# LANGUAGE TemplateHaskell, TypeSynonymInstances, FlexibleInstances #-}
2 e5a29b6c Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e5a29b6c Iustin Pop
4 e5a29b6c Iustin Pop
{-| Unittests for ganeti-htools.
5 e5a29b6c Iustin Pop
6 e5a29b6c Iustin Pop
-}
7 e5a29b6c Iustin Pop
8 e5a29b6c Iustin Pop
{-
9 e5a29b6c Iustin Pop
10 72747d91 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 e5a29b6c Iustin Pop
12 e5a29b6c Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e5a29b6c Iustin Pop
it under the terms of the GNU General Public License as published by
14 e5a29b6c Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e5a29b6c Iustin Pop
(at your option) any later version.
16 e5a29b6c Iustin Pop
17 e5a29b6c Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e5a29b6c Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e5a29b6c Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e5a29b6c Iustin Pop
General Public License for more details.
21 e5a29b6c Iustin Pop
22 e5a29b6c Iustin Pop
You should have received a copy of the GNU General Public License
23 e5a29b6c Iustin Pop
along with this program; if not, write to the Free Software
24 e5a29b6c Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e5a29b6c Iustin Pop
02110-1301, USA.
26 e5a29b6c Iustin Pop
27 e5a29b6c Iustin Pop
-}
28 e5a29b6c Iustin Pop
29 305e174c Iustin Pop
module Test.Ganeti.Objects
30 305e174c Iustin Pop
  ( testObjects
31 8d2b6a12 Iustin Pop
  , Node(..)
32 9924d61e Iustin Pop
  , genEmptyCluster
33 0b288282 Helga Velroyen
  , genValidNetwork
34 0b288282 Helga Velroyen
  , genBitStringMaxLen
35 305e174c Iustin Pop
  ) where
36 e5a29b6c Iustin Pop
37 8d2b6a12 Iustin Pop
import Test.QuickCheck
38 0b288282 Helga Velroyen
import qualified Test.HUnit as HUnit
39 8d2b6a12 Iustin Pop
40 305e174c Iustin Pop
import Control.Applicative
41 0b288282 Helga Velroyen
import Control.Monad
42 0b288282 Helga Velroyen
import Data.Char
43 e5a29b6c Iustin Pop
import qualified Data.Map as Map
44 305e174c Iustin Pop
import qualified Data.Set as Set
45 0b288282 Helga Velroyen
import qualified Text.JSON as J
46 e5a29b6c Iustin Pop
47 e5a29b6c Iustin Pop
import Test.Ganeti.TestHelper
48 305e174c Iustin Pop
import Test.Ganeti.TestCommon
49 5e9deac0 Iustin Pop
import Test.Ganeti.Types ()
50 9924d61e Iustin Pop
51 9924d61e Iustin Pop
import qualified Ganeti.Constants as C
52 0b288282 Helga Velroyen
import Ganeti.Network
53 8d2b6a12 Iustin Pop
import Ganeti.Objects as Objects
54 ce93b4a0 Iustin Pop
import Ganeti.JSON
55 0b288282 Helga Velroyen
import Ganeti.Types
56 8d2b6a12 Iustin Pop
57 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
58 5b11f8db Iustin Pop
59 8d2b6a12 Iustin Pop
-- * Arbitrary instances
60 e5a29b6c Iustin Pop
61 7022db83 Iustin Pop
$(genArbitrary ''PartialNDParams)
62 305e174c Iustin Pop
63 8d2b6a12 Iustin Pop
instance Arbitrary Node where
64 5006418e Iustin Pop
  arbitrary = Node <$> genFQDN <*> genFQDN <*> genFQDN
65 5006418e Iustin Pop
              <*> arbitrary <*> arbitrary <*> arbitrary <*> genFQDN
66 305e174c Iustin Pop
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
67 5006418e Iustin Pop
              <*> arbitrary <*> arbitrary <*> genFQDN <*> arbitrary
68 305e174c Iustin Pop
              <*> (Set.fromList <$> genTags)
69 305e174c Iustin Pop
70 7022db83 Iustin Pop
$(genArbitrary ''BlockDriver)
71 8d2b6a12 Iustin Pop
72 7022db83 Iustin Pop
$(genArbitrary ''DiskMode)
73 8d2b6a12 Iustin Pop
74 8d2b6a12 Iustin Pop
instance Arbitrary DiskLogicalId where
75 8d2b6a12 Iustin Pop
  arbitrary = oneof [ LIDPlain <$> arbitrary <*> arbitrary
76 5006418e Iustin Pop
                    , LIDDrbd8 <$> genFQDN <*> genFQDN <*> arbitrary
77 8d2b6a12 Iustin Pop
                               <*> arbitrary <*> arbitrary <*> arbitrary
78 8d2b6a12 Iustin Pop
                    , LIDFile  <$> arbitrary <*> arbitrary
79 8d2b6a12 Iustin Pop
                    , LIDBlockDev <$> arbitrary <*> arbitrary
80 8d2b6a12 Iustin Pop
                    , LIDRados <$> arbitrary <*> arbitrary
81 8d2b6a12 Iustin Pop
                    ]
82 8d2b6a12 Iustin Pop
83 8d2b6a12 Iustin Pop
-- | 'Disk' 'arbitrary' instance. Since we don't test disk hierarchy
84 8d2b6a12 Iustin Pop
-- properties, we only generate disks with no children (FIXME), as
85 8d2b6a12 Iustin Pop
-- generating recursive datastructures is a bit more work.
86 8d2b6a12 Iustin Pop
instance Arbitrary Disk where
87 5b11f8db Iustin Pop
  arbitrary = Disk <$> arbitrary <*> pure [] <*> arbitrary
88 8d2b6a12 Iustin Pop
                   <*> arbitrary <*> arbitrary
89 8d2b6a12 Iustin Pop
90 7022db83 Iustin Pop
-- FIXME: we should generate proper values, >=0, etc., but this is
91 7022db83 Iustin Pop
-- hard for partial ones, where all must be wrapped in a 'Maybe'
92 7022db83 Iustin Pop
$(genArbitrary ''PartialBeParams)
93 ce93b4a0 Iustin Pop
94 7022db83 Iustin Pop
$(genArbitrary ''AdminState)
95 ce93b4a0 Iustin Pop
96 7022db83 Iustin Pop
$(genArbitrary ''PartialNicParams)
97 ce93b4a0 Iustin Pop
98 7022db83 Iustin Pop
$(genArbitrary ''PartialNic)
99 ce93b4a0 Iustin Pop
100 ce93b4a0 Iustin Pop
instance Arbitrary Instance where
101 ce93b4a0 Iustin Pop
  arbitrary =
102 ce93b4a0 Iustin Pop
    Instance
103 5006418e Iustin Pop
      <$> genFQDN <*> genFQDN <*> genFQDN -- OS name, but...
104 ce93b4a0 Iustin Pop
      <*> arbitrary
105 ce93b4a0 Iustin Pop
      -- FIXME: add non-empty hvparams when they're a proper type
106 edc1acde Iustin Pop
      <*> pure (GenericContainer Map.empty) <*> arbitrary
107 ce93b4a0 Iustin Pop
      -- ... and for OSParams
108 edc1acde Iustin Pop
      <*> pure (GenericContainer Map.empty) <*> arbitrary <*> arbitrary
109 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary <*> arbitrary
110 ce93b4a0 Iustin Pop
      -- ts
111 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary
112 ce93b4a0 Iustin Pop
      -- uuid
113 ce93b4a0 Iustin Pop
      <*> arbitrary
114 ce93b4a0 Iustin Pop
      -- serial
115 ce93b4a0 Iustin Pop
      <*> arbitrary
116 ce93b4a0 Iustin Pop
      -- tags
117 ce93b4a0 Iustin Pop
      <*> (Set.fromList <$> genTags)
118 ce93b4a0 Iustin Pop
119 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
120 9924d61e Iustin Pop
-- validation rules.
121 9924d61e Iustin Pop
$(genArbitrary ''PartialISpecParams)
122 9924d61e Iustin Pop
123 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
124 9924d61e Iustin Pop
-- validation rules.
125 9924d61e Iustin Pop
$(genArbitrary ''PartialIPolicy)
126 9924d61e Iustin Pop
127 9924d61e Iustin Pop
$(genArbitrary ''FilledISpecParams)
128 9924d61e Iustin Pop
$(genArbitrary ''FilledIPolicy)
129 9924d61e Iustin Pop
$(genArbitrary ''IpFamily)
130 9924d61e Iustin Pop
$(genArbitrary ''FilledNDParams)
131 9924d61e Iustin Pop
$(genArbitrary ''FilledNicParams)
132 9924d61e Iustin Pop
$(genArbitrary ''FilledBeParams)
133 9924d61e Iustin Pop
134 9924d61e Iustin Pop
-- | No real arbitrary instance for 'ClusterHvParams' yet.
135 9924d61e Iustin Pop
instance Arbitrary ClusterHvParams where
136 edc1acde Iustin Pop
  arbitrary = return $ GenericContainer Map.empty
137 9924d61e Iustin Pop
138 9924d61e Iustin Pop
-- | No real arbitrary instance for 'OsHvParams' yet.
139 9924d61e Iustin Pop
instance Arbitrary OsHvParams where
140 edc1acde Iustin Pop
  arbitrary = return $ GenericContainer Map.empty
141 9924d61e Iustin Pop
142 9924d61e Iustin Pop
instance Arbitrary ClusterNicParams where
143 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.singleton C.ppDefault) <$> arbitrary
144 9924d61e Iustin Pop
145 9924d61e Iustin Pop
instance Arbitrary OsParams where
146 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
147 9924d61e Iustin Pop
148 9924d61e Iustin Pop
instance Arbitrary ClusterOsParams where
149 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
150 9924d61e Iustin Pop
151 9924d61e Iustin Pop
instance Arbitrary ClusterBeParams where
152 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
153 9924d61e Iustin Pop
154 9924d61e Iustin Pop
instance Arbitrary TagSet where
155 9924d61e Iustin Pop
  arbitrary = Set.fromList <$> genTags
156 9924d61e Iustin Pop
157 9924d61e Iustin Pop
$(genArbitrary ''Cluster)
158 9924d61e Iustin Pop
159 76a0266e Helga Velroyen
instance Arbitrary Network where
160 0b288282 Helga Velroyen
  arbitrary = genValidNetwork
161 0b288282 Helga Velroyen
162 0b288282 Helga Velroyen
-- | Generates a network instance with minimum netmasks of /24. Generating
163 0b288282 Helga Velroyen
-- bigger networks slows down the tests, because long bit strings are generated
164 0b288282 Helga Velroyen
-- for the reservations.
165 0b288282 Helga Velroyen
genValidNetwork :: Gen Objects.Network
166 0b288282 Helga Velroyen
genValidNetwork = do
167 0b288282 Helga Velroyen
  -- generate netmask for the IPv4 network
168 0b288282 Helga Velroyen
  netmask <- choose (24::Int, 30)
169 0b288282 Helga Velroyen
  name <- genName >>= mkNonEmpty
170 0b288282 Helga Velroyen
  mac_prefix <- genMaybe genName
171 0b288282 Helga Velroyen
  net <- genIp4NetWithNetmask netmask
172 0b288282 Helga Velroyen
  net6 <- genMaybe genIp6Net
173 0b288282 Helga Velroyen
  gateway <- genMaybe genIp4AddrStr
174 0b288282 Helga Velroyen
  gateway6 <- genMaybe genIp6Addr
175 0b288282 Helga Velroyen
  res <- liftM Just (genBitString $ netmask2NumHosts netmask)
176 0b288282 Helga Velroyen
  ext_res <- liftM Just (genBitString $ netmask2NumHosts netmask)
177 5cfa6c37 Dimitris Aragiorgis
  let n = Network name mac_prefix net net6 gateway
178 5cfa6c37 Dimitris Aragiorgis
          gateway6 res ext_res 0 Set.empty
179 0b288282 Helga Velroyen
  return n
180 0b288282 Helga Velroyen
181 0b288282 Helga Velroyen
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
182 0b288282 Helga Velroyen
genBitString :: Int -> Gen String
183 0b288282 Helga Velroyen
genBitString len = vectorOf len (elements "01")
184 0b288282 Helga Velroyen
185 0b288282 Helga Velroyen
-- | Generate an arbitrary string consisting of '0' and '1' of the maximum given
186 0b288282 Helga Velroyen
-- length.
187 0b288282 Helga Velroyen
genBitStringMaxLen :: Int -> Gen String
188 0b288282 Helga Velroyen
genBitStringMaxLen maxLen = choose (0, maxLen) >>= genBitString
189 76a0266e Helga Velroyen
190 9924d61e Iustin Pop
-- | Generator for config data with an empty cluster (no instances),
191 9924d61e Iustin Pop
-- with N defined nodes.
192 9924d61e Iustin Pop
genEmptyCluster :: Int -> Gen ConfigData
193 9924d61e Iustin Pop
genEmptyCluster ncount = do
194 9924d61e Iustin Pop
  nodes <- vector ncount
195 9924d61e Iustin Pop
  version <- arbitrary
196 9924d61e Iustin Pop
  let guuid = "00"
197 5f4fdf93 Iustin Pop
      nodes' = zipWith (\n idx ->
198 5f4fdf93 Iustin Pop
                          let newname = nodeName n ++ "-" ++ show idx
199 5f4fdf93 Iustin Pop
                          in (newname, n { nodeGroup = guuid,
200 5f4fdf93 Iustin Pop
                                           nodeName = newname}))
201 b9bdc10e Iustin Pop
               nodes [(1::Int)..]
202 5f4fdf93 Iustin Pop
      nodemap = Map.fromList nodes'
203 5f4fdf93 Iustin Pop
      contnodes = if Map.size nodemap /= ncount
204 5f4fdf93 Iustin Pop
                    then error ("Inconsistent node map, duplicates in" ++
205 5f4fdf93 Iustin Pop
                                " node name list? Names: " ++
206 5f4fdf93 Iustin Pop
                                show (map fst nodes'))
207 5f4fdf93 Iustin Pop
                    else GenericContainer nodemap
208 edc1acde Iustin Pop
      continsts = GenericContainer Map.empty
209 9924d61e Iustin Pop
  grp <- arbitrary
210 edc1acde Iustin Pop
  let contgroups = GenericContainer $ Map.singleton guuid grp
211 9924d61e Iustin Pop
  serial <- arbitrary
212 c3a8e06d Iustin Pop
  cluster <- resize 8 arbitrary
213 9924d61e Iustin Pop
  let c = ConfigData version cluster contnodes contgroups continsts serial
214 9924d61e Iustin Pop
  return c
215 9924d61e Iustin Pop
216 8d2b6a12 Iustin Pop
-- * Test properties
217 8d2b6a12 Iustin Pop
218 e5a29b6c Iustin Pop
-- | Tests that fillDict behaves correctly
219 20bc5360 Iustin Pop
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
220 20bc5360 Iustin Pop
prop_fillDict defaults custom =
221 e5a29b6c Iustin Pop
  let d_map = Map.fromList defaults
222 e5a29b6c Iustin Pop
      d_keys = map fst defaults
223 e5a29b6c Iustin Pop
      c_map = Map.fromList custom
224 e5a29b6c Iustin Pop
      c_keys = map fst custom
225 942a9a6a Iustin Pop
  in conjoin [ printTestCase "Empty custom filling"
226 942a9a6a Iustin Pop
               (fillDict d_map Map.empty [] == d_map)
227 942a9a6a Iustin Pop
             , printTestCase "Empty defaults filling"
228 942a9a6a Iustin Pop
               (fillDict Map.empty c_map [] == c_map)
229 942a9a6a Iustin Pop
             , printTestCase "Delete all keys"
230 942a9a6a Iustin Pop
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
231 942a9a6a Iustin Pop
             ]
232 8d2b6a12 Iustin Pop
233 8d2b6a12 Iustin Pop
-- | Test that the serialisation of 'DiskLogicalId', which is
234 8d2b6a12 Iustin Pop
-- implemented manually, is idempotent. Since we don't have a
235 8d2b6a12 Iustin Pop
-- standalone JSON instance for DiskLogicalId (it's a data type that
236 8d2b6a12 Iustin Pop
-- expands over two fields in a JSObject), we test this by actially
237 8d2b6a12 Iustin Pop
-- testing entire Disk serialisations. So this tests two things at
238 8d2b6a12 Iustin Pop
-- once, basically.
239 8d2b6a12 Iustin Pop
prop_Disk_serialisation :: Disk -> Property
240 63b068c1 Iustin Pop
prop_Disk_serialisation = testSerialisation
241 8d2b6a12 Iustin Pop
242 8d2b6a12 Iustin Pop
-- | Check that node serialisation is idempotent.
243 8d2b6a12 Iustin Pop
prop_Node_serialisation :: Node -> Property
244 63b068c1 Iustin Pop
prop_Node_serialisation = testSerialisation
245 e5a29b6c Iustin Pop
246 ce93b4a0 Iustin Pop
-- | Check that instance serialisation is idempotent.
247 ce93b4a0 Iustin Pop
prop_Inst_serialisation :: Instance -> Property
248 ce93b4a0 Iustin Pop
prop_Inst_serialisation = testSerialisation
249 ce93b4a0 Iustin Pop
250 76a0266e Helga Velroyen
-- | Check that network serialisation is idempotent.
251 76a0266e Helga Velroyen
prop_Network_serialisation :: Network -> Property
252 76a0266e Helga Velroyen
prop_Network_serialisation = testSerialisation
253 76a0266e Helga Velroyen
254 9924d61e Iustin Pop
-- | Check config serialisation.
255 9924d61e Iustin Pop
prop_Config_serialisation :: Property
256 9924d61e Iustin Pop
prop_Config_serialisation =
257 c3a8e06d Iustin Pop
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
258 9924d61e Iustin Pop
259 0b288282 Helga Velroyen
-- | Custom HUnit test to check the correspondence between Haskell-generated
260 0b288282 Helga Velroyen
-- networks and their Python decoded, validated and re-encoded version.
261 0b288282 Helga Velroyen
-- For the technical background of this unit test, check the documentation
262 83846468 Iustin Pop
-- of "case_py_compat_types" of test/hs/Test/Ganeti/Opcodes.hs
263 0b288282 Helga Velroyen
case_py_compat_networks :: HUnit.Assertion
264 0b288282 Helga Velroyen
case_py_compat_networks = do
265 0b288282 Helga Velroyen
  let num_networks = 500::Int
266 72747d91 Iustin Pop
  networks <- genSample (vectorOf num_networks genValidNetwork)
267 72747d91 Iustin Pop
  let networks_with_properties = map getNetworkProperties networks
268 0b288282 Helga Velroyen
      serialized = J.encode networks
269 0b288282 Helga Velroyen
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
270 0b288282 Helga Velroyen
  mapM_ (\net -> when (any (not . isAscii) (J.encode net)) .
271 0b288282 Helga Velroyen
                 HUnit.assertFailure $
272 0b288282 Helga Velroyen
                 "Network has non-ASCII fields: " ++ show net
273 0b288282 Helga Velroyen
        ) networks
274 0b288282 Helga Velroyen
  py_stdout <-
275 0b288282 Helga Velroyen
    runPython "from ganeti import network\n\
276 0b288282 Helga Velroyen
              \from ganeti import objects\n\
277 0b288282 Helga Velroyen
              \from ganeti import serializer\n\
278 0b288282 Helga Velroyen
              \import sys\n\
279 0b288282 Helga Velroyen
              \net_data = serializer.Load(sys.stdin.read())\n\
280 0b288282 Helga Velroyen
              \decoded = [objects.Network.FromDict(n) for n in net_data]\n\
281 0b288282 Helga Velroyen
              \encoded = []\n\
282 0b288282 Helga Velroyen
              \for net in decoded:\n\
283 0b288282 Helga Velroyen
              \  a = network.AddressPool(net)\n\
284 0b288282 Helga Velroyen
              \  encoded.append((a.GetFreeCount(), a.GetReservedCount(), \\\n\
285 0b288282 Helga Velroyen
              \    net.ToDict()))\n\
286 0b288282 Helga Velroyen
              \print serializer.Dump(encoded)" serialized
287 0b288282 Helga Velroyen
    >>= checkPythonResult
288 0b288282 Helga Velroyen
  let deserialised = J.decode py_stdout::J.Result [(Int, Int, Network)]
289 0b288282 Helga Velroyen
  decoded <- case deserialised of
290 0b288282 Helga Velroyen
               J.Ok ops -> return ops
291 0b288282 Helga Velroyen
               J.Error msg ->
292 0b288282 Helga Velroyen
                 HUnit.assertFailure ("Unable to decode networks: " ++ msg)
293 0b288282 Helga Velroyen
                 -- this already raised an expection, but we need it
294 0b288282 Helga Velroyen
                 -- for proper types
295 0b288282 Helga Velroyen
                 >> fail "Unable to decode networks"
296 0b288282 Helga Velroyen
  HUnit.assertEqual "Mismatch in number of returned networks"
297 0b288282 Helga Velroyen
    (length decoded) (length networks_with_properties)
298 0b288282 Helga Velroyen
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
299 0b288282 Helga Velroyen
        ) $ zip decoded networks_with_properties
300 0b288282 Helga Velroyen
301 0b288282 Helga Velroyen
-- | Creates a tuple of the given network combined with some of its properties
302 0b288282 Helga Velroyen
-- to be compared against the same properties generated by the python code.
303 0b288282 Helga Velroyen
getNetworkProperties :: Network -> (Int, Int, Network)
304 0b288282 Helga Velroyen
getNetworkProperties net =
305 0b288282 Helga Velroyen
  let maybePool = createAddressPool net
306 0b288282 Helga Velroyen
  in  case maybePool of
307 0b288282 Helga Velroyen
           (Just pool) -> (getFreeCount pool, getReservedCount pool, net)
308 0b288282 Helga Velroyen
           Nothing -> (-1, -1, net)
309 0b288282 Helga Velroyen
310 5b48df93 Helga Velroyen
-- | Tests the compatibility between Haskell-serialized node groups and their
311 5b48df93 Helga Velroyen
-- python-decoded and encoded version.
312 5b48df93 Helga Velroyen
case_py_compat_nodegroups :: HUnit.Assertion
313 5b48df93 Helga Velroyen
case_py_compat_nodegroups = do
314 5b48df93 Helga Velroyen
  let num_groups = 500::Int
315 72747d91 Iustin Pop
  groups <- genSample (vectorOf num_groups genNodeGroup)
316 72747d91 Iustin Pop
  let serialized = J.encode groups
317 5b48df93 Helga Velroyen
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
318 5b48df93 Helga Velroyen
  mapM_ (\group -> when (any (not . isAscii) (J.encode group)) .
319 5b48df93 Helga Velroyen
                 HUnit.assertFailure $
320 5b48df93 Helga Velroyen
                 "Node group has non-ASCII fields: " ++ show group
321 5b48df93 Helga Velroyen
        ) groups
322 5b48df93 Helga Velroyen
  py_stdout <-
323 5b48df93 Helga Velroyen
    runPython "from ganeti import objects\n\
324 5b48df93 Helga Velroyen
              \from ganeti import serializer\n\
325 5b48df93 Helga Velroyen
              \import sys\n\
326 5b48df93 Helga Velroyen
              \group_data = serializer.Load(sys.stdin.read())\n\
327 5b48df93 Helga Velroyen
              \decoded = [objects.NodeGroup.FromDict(g) for g in group_data]\n\
328 5b48df93 Helga Velroyen
              \encoded = [g.ToDict() for g in decoded]\n\
329 5b48df93 Helga Velroyen
              \print serializer.Dump(encoded)" serialized
330 5b48df93 Helga Velroyen
    >>= checkPythonResult
331 5b48df93 Helga Velroyen
  let deserialised = J.decode py_stdout::J.Result [NodeGroup]
332 5b48df93 Helga Velroyen
  decoded <- case deserialised of
333 5b48df93 Helga Velroyen
               J.Ok ops -> return ops
334 5b48df93 Helga Velroyen
               J.Error msg ->
335 5b48df93 Helga Velroyen
                 HUnit.assertFailure ("Unable to decode node groups: " ++ msg)
336 5b48df93 Helga Velroyen
                 -- this already raised an expection, but we need it
337 5b48df93 Helga Velroyen
                 -- for proper types
338 5b48df93 Helga Velroyen
                 >> fail "Unable to decode node groups"
339 5b48df93 Helga Velroyen
  HUnit.assertEqual "Mismatch in number of returned node groups"
340 5b48df93 Helga Velroyen
    (length decoded) (length groups)
341 5b48df93 Helga Velroyen
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
342 5b48df93 Helga Velroyen
        ) $ zip decoded groups
343 5b48df93 Helga Velroyen
344 5b48df93 Helga Velroyen
-- | Generates a node group with up to 3 networks.
345 5b48df93 Helga Velroyen
-- | FIXME: This generates still somewhat completely random data, without normal
346 5b48df93 Helga Velroyen
-- validation rules.
347 5b48df93 Helga Velroyen
genNodeGroup :: Gen NodeGroup
348 5b48df93 Helga Velroyen
genNodeGroup = do
349 5b48df93 Helga Velroyen
  name <- genFQDN
350 5b48df93 Helga Velroyen
  members <- pure []
351 5b48df93 Helga Velroyen
  ndparams <- arbitrary
352 5b48df93 Helga Velroyen
  alloc_policy <- arbitrary
353 5b48df93 Helga Velroyen
  ipolicy <- arbitrary
354 5b48df93 Helga Velroyen
  diskparams <- pure (GenericContainer Map.empty)
355 5b48df93 Helga Velroyen
  num_networks <- choose (0, 3)
356 da1dcce1 Helga Velroyen
  net_uuid_list <- vectorOf num_networks (arbitrary::Gen String)
357 2f3a3365 Helga Velroyen
  nic_param_list <- vectorOf num_networks (arbitrary::Gen PartialNicParams)
358 da1dcce1 Helga Velroyen
  net_map <- pure (GenericContainer . Map.fromList $
359 da1dcce1 Helga Velroyen
    zip net_uuid_list nic_param_list)
360 5b48df93 Helga Velroyen
  -- timestamp fields
361 5b48df93 Helga Velroyen
  ctime <- arbitrary
362 5b48df93 Helga Velroyen
  mtime <- arbitrary
363 5b48df93 Helga Velroyen
  uuid <- arbitrary
364 5b48df93 Helga Velroyen
  serial <- arbitrary
365 5b48df93 Helga Velroyen
  tags <- Set.fromList <$> genTags
366 5b48df93 Helga Velroyen
  let group = NodeGroup name members ndparams alloc_policy ipolicy diskparams
367 da1dcce1 Helga Velroyen
              net_map ctime mtime uuid serial tags
368 5b48df93 Helga Velroyen
  return group
369 5b48df93 Helga Velroyen
370 5b48df93 Helga Velroyen
instance Arbitrary NodeGroup where
371 5b48df93 Helga Velroyen
  arbitrary = genNodeGroup
372 5b48df93 Helga Velroyen
373 e5a29b6c Iustin Pop
testSuite "Objects"
374 20bc5360 Iustin Pop
  [ 'prop_fillDict
375 8d2b6a12 Iustin Pop
  , 'prop_Disk_serialisation
376 ce93b4a0 Iustin Pop
  , 'prop_Inst_serialisation
377 76a0266e Helga Velroyen
  , 'prop_Network_serialisation
378 8d2b6a12 Iustin Pop
  , 'prop_Node_serialisation
379 44be51aa Iustin Pop
  , 'prop_Config_serialisation
380 0b288282 Helga Velroyen
  , 'case_py_compat_networks
381 5b48df93 Helga Velroyen
  , 'case_py_compat_nodegroups
382 9924d61e Iustin Pop
  ]