Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ da5f09ef

History | View | Annotate | Download (16.7 kB)

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