Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Objects.hs @ 712da82f

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