Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 4e4433e8

History | View | Annotate | Download (16.8 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 3c1a8730 Christos Stavrakakis
                   <*> arbitrary <*> arbitrary <*> arbitrary
93 3c1a8730 Christos Stavrakakis
                   <*> arbitrary
94 8d2b6a12 Iustin Pop
95 7022db83 Iustin Pop
-- FIXME: we should generate proper values, >=0, etc., but this is
96 7022db83 Iustin Pop
-- hard for partial ones, where all must be wrapped in a 'Maybe'
97 7022db83 Iustin Pop
$(genArbitrary ''PartialBeParams)
98 ce93b4a0 Iustin Pop
99 7022db83 Iustin Pop
$(genArbitrary ''AdminState)
100 ce93b4a0 Iustin Pop
101 7022db83 Iustin Pop
$(genArbitrary ''PartialNicParams)
102 ce93b4a0 Iustin Pop
103 7022db83 Iustin Pop
$(genArbitrary ''PartialNic)
104 ce93b4a0 Iustin Pop
105 ce93b4a0 Iustin Pop
instance Arbitrary Instance where
106 ce93b4a0 Iustin Pop
  arbitrary =
107 ce93b4a0 Iustin Pop
    Instance
108 5006418e Iustin Pop
      <$> genFQDN <*> genFQDN <*> genFQDN -- OS name, but...
109 ce93b4a0 Iustin Pop
      <*> arbitrary
110 ce93b4a0 Iustin Pop
      -- FIXME: add non-empty hvparams when they're a proper type
111 edc1acde Iustin Pop
      <*> pure (GenericContainer Map.empty) <*> arbitrary
112 ce93b4a0 Iustin Pop
      -- ... and for OSParams
113 edc1acde Iustin Pop
      <*> pure (GenericContainer Map.empty) <*> arbitrary <*> arbitrary
114 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary <*> arbitrary
115 ce93b4a0 Iustin Pop
      -- ts
116 ce93b4a0 Iustin Pop
      <*> arbitrary <*> arbitrary
117 ce93b4a0 Iustin Pop
      -- uuid
118 ce93b4a0 Iustin Pop
      <*> arbitrary
119 ce93b4a0 Iustin Pop
      -- serial
120 ce93b4a0 Iustin Pop
      <*> arbitrary
121 ce93b4a0 Iustin Pop
      -- tags
122 ce93b4a0 Iustin Pop
      <*> (Set.fromList <$> genTags)
123 ce93b4a0 Iustin Pop
124 834bea99 Helga Velroyen
-- | Generates an instance that is connected to the given networks
125 834bea99 Helga Velroyen
-- and possibly some other networks
126 834bea99 Helga Velroyen
genInstWithNets :: [String] -> Gen Instance
127 834bea99 Helga Velroyen
genInstWithNets nets = do
128 834bea99 Helga Velroyen
  plain_inst <- arbitrary
129 834bea99 Helga Velroyen
  mac <- arbitrary
130 834bea99 Helga Velroyen
  ip <- arbitrary
131 834bea99 Helga Velroyen
  nicparams <- arbitrary
132 3c1a8730 Christos Stavrakakis
  name <- arbitrary
133 3c1a8730 Christos Stavrakakis
  uuid <- arbitrary
134 834bea99 Helga Velroyen
  -- generate some more networks than the given ones
135 834bea99 Helga Velroyen
  num_more_nets <- choose (0,3)
136 834bea99 Helga Velroyen
  more_nets <- vectorOf num_more_nets genName
137 3c1a8730 Christos Stavrakakis
  let genNic net = PartialNic mac ip nicparams net name uuid
138 3c1a8730 Christos Stavrakakis
      partial_nics = map (genNic . Just)
139 3c1a8730 Christos Stavrakakis
                         (List.nub (nets ++ more_nets))
140 834bea99 Helga Velroyen
      new_inst = plain_inst { instNics = partial_nics }
141 834bea99 Helga Velroyen
  return new_inst
142 834bea99 Helga Velroyen
143 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
144 9924d61e Iustin Pop
-- validation rules.
145 9924d61e Iustin Pop
$(genArbitrary ''PartialISpecParams)
146 da5f09ef Bernardo Dal Seno
$(genArbitrary ''PartialMinMaxISpecs)
147 9924d61e Iustin Pop
148 9924d61e Iustin Pop
-- | FIXME: This generates completely random data, without normal
149 9924d61e Iustin Pop
-- validation rules.
150 9924d61e Iustin Pop
$(genArbitrary ''PartialIPolicy)
151 9924d61e Iustin Pop
152 9924d61e Iustin Pop
$(genArbitrary ''FilledISpecParams)
153 da5f09ef Bernardo Dal Seno
$(genArbitrary ''FilledMinMaxISpecs)
154 9924d61e Iustin Pop
$(genArbitrary ''FilledIPolicy)
155 9924d61e Iustin Pop
$(genArbitrary ''IpFamily)
156 9924d61e Iustin Pop
$(genArbitrary ''FilledNDParams)
157 9924d61e Iustin Pop
$(genArbitrary ''FilledNicParams)
158 9924d61e Iustin Pop
$(genArbitrary ''FilledBeParams)
159 9924d61e Iustin Pop
160 9924d61e Iustin Pop
-- | No real arbitrary instance for 'ClusterHvParams' yet.
161 9924d61e Iustin Pop
instance Arbitrary ClusterHvParams where
162 edc1acde Iustin Pop
  arbitrary = return $ GenericContainer Map.empty
163 9924d61e Iustin Pop
164 9924d61e Iustin Pop
-- | No real arbitrary instance for 'OsHvParams' yet.
165 9924d61e Iustin Pop
instance Arbitrary OsHvParams where
166 edc1acde Iustin Pop
  arbitrary = return $ GenericContainer Map.empty
167 9924d61e Iustin Pop
168 9924d61e Iustin Pop
instance Arbitrary ClusterNicParams where
169 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.singleton C.ppDefault) <$> arbitrary
170 9924d61e Iustin Pop
171 9924d61e Iustin Pop
instance Arbitrary OsParams where
172 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
173 9924d61e Iustin Pop
174 9924d61e Iustin Pop
instance Arbitrary ClusterOsParams where
175 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
176 9924d61e Iustin Pop
177 9924d61e Iustin Pop
instance Arbitrary ClusterBeParams where
178 edc1acde Iustin Pop
  arbitrary = (GenericContainer . Map.fromList) <$> arbitrary
179 9924d61e Iustin Pop
180 9924d61e Iustin Pop
instance Arbitrary TagSet where
181 9924d61e Iustin Pop
  arbitrary = Set.fromList <$> genTags
182 9924d61e Iustin Pop
183 9924d61e Iustin Pop
$(genArbitrary ''Cluster)
184 9924d61e Iustin Pop
185 76a0266e Helga Velroyen
instance Arbitrary Network where
186 0b288282 Helga Velroyen
  arbitrary = genValidNetwork
187 0b288282 Helga Velroyen
188 0b288282 Helga Velroyen
-- | Generates a network instance with minimum netmasks of /24. Generating
189 0b288282 Helga Velroyen
-- bigger networks slows down the tests, because long bit strings are generated
190 0b288282 Helga Velroyen
-- for the reservations.
191 0b288282 Helga Velroyen
genValidNetwork :: Gen Objects.Network
192 0b288282 Helga Velroyen
genValidNetwork = do
193 0b288282 Helga Velroyen
  -- generate netmask for the IPv4 network
194 3a991f2d Iustin Pop
  netmask <- fromIntegral <$> choose (24::Int, 30)
195 0b288282 Helga Velroyen
  name <- genName >>= mkNonEmpty
196 0b288282 Helga Velroyen
  mac_prefix <- genMaybe genName
197 3a991f2d Iustin Pop
  net <- arbitrary
198 0b288282 Helga Velroyen
  net6 <- genMaybe genIp6Net
199 3a991f2d Iustin Pop
  gateway <- genMaybe arbitrary
200 0b288282 Helga Velroyen
  gateway6 <- genMaybe genIp6Addr
201 0b288282 Helga Velroyen
  res <- liftM Just (genBitString $ netmask2NumHosts netmask)
202 0b288282 Helga Velroyen
  ext_res <- liftM Just (genBitString $ netmask2NumHosts netmask)
203 b43064d0 Helga Velroyen
  uuid <- arbitrary
204 3a991f2d Iustin Pop
  let n = Network name mac_prefix (Ip4Network net netmask) net6 gateway
205 3c296f56 Michael Hanselmann
          gateway6 res ext_res uuid 0 Set.empty
206 0b288282 Helga Velroyen
  return n
207 0b288282 Helga Velroyen
208 0b288282 Helga Velroyen
-- | Generate an arbitrary string consisting of '0' and '1' of the given length.
209 0b288282 Helga Velroyen
genBitString :: Int -> Gen String
210 0b288282 Helga Velroyen
genBitString len = vectorOf len (elements "01")
211 0b288282 Helga Velroyen
212 0b288282 Helga Velroyen
-- | Generate an arbitrary string consisting of '0' and '1' of the maximum given
213 0b288282 Helga Velroyen
-- length.
214 0b288282 Helga Velroyen
genBitStringMaxLen :: Int -> Gen String
215 0b288282 Helga Velroyen
genBitStringMaxLen maxLen = choose (0, maxLen) >>= genBitString
216 76a0266e Helga Velroyen
217 9924d61e Iustin Pop
-- | Generator for config data with an empty cluster (no instances),
218 9924d61e Iustin Pop
-- with N defined nodes.
219 9924d61e Iustin Pop
genEmptyCluster :: Int -> Gen ConfigData
220 9924d61e Iustin Pop
genEmptyCluster ncount = do
221 9924d61e Iustin Pop
  nodes <- vector ncount
222 9924d61e Iustin Pop
  version <- arbitrary
223 e7124835 Iustin Pop
  grp <- arbitrary
224 e7124835 Iustin Pop
  let guuid = groupUuid grp
225 5f4fdf93 Iustin Pop
      nodes' = zipWith (\n idx ->
226 5f4fdf93 Iustin Pop
                          let newname = nodeName n ++ "-" ++ show idx
227 5f4fdf93 Iustin Pop
                          in (newname, n { nodeGroup = guuid,
228 5f4fdf93 Iustin Pop
                                           nodeName = newname}))
229 b9bdc10e Iustin Pop
               nodes [(1::Int)..]
230 5f4fdf93 Iustin Pop
      nodemap = Map.fromList nodes'
231 5f4fdf93 Iustin Pop
      contnodes = if Map.size nodemap /= ncount
232 5f4fdf93 Iustin Pop
                    then error ("Inconsistent node map, duplicates in" ++
233 5f4fdf93 Iustin Pop
                                " node name list? Names: " ++
234 5f4fdf93 Iustin Pop
                                show (map fst nodes'))
235 5f4fdf93 Iustin Pop
                    else GenericContainer nodemap
236 edc1acde Iustin Pop
      continsts = GenericContainer Map.empty
237 b43064d0 Helga Velroyen
      networks = GenericContainer Map.empty
238 edc1acde Iustin Pop
  let contgroups = GenericContainer $ Map.singleton guuid grp
239 9924d61e Iustin Pop
  serial <- arbitrary
240 c3a8e06d Iustin Pop
  cluster <- resize 8 arbitrary
241 b43064d0 Helga Velroyen
  let c = ConfigData version cluster contnodes contgroups continsts networks
242 b43064d0 Helga Velroyen
            serial
243 9924d61e Iustin Pop
  return c
244 9924d61e Iustin Pop
245 834bea99 Helga Velroyen
-- | FIXME: make an even simpler base version of creating a cluster.
246 834bea99 Helga Velroyen
247 834bea99 Helga Velroyen
-- | Generates config data with a couple of networks.
248 834bea99 Helga Velroyen
genConfigDataWithNetworks :: ConfigData -> Gen ConfigData
249 834bea99 Helga Velroyen
genConfigDataWithNetworks old_cfg = do
250 834bea99 Helga Velroyen
  num_nets <- choose (0, 3)
251 834bea99 Helga Velroyen
  -- generate a list of network names (no duplicates)
252 834bea99 Helga Velroyen
  net_names <- genUniquesList num_nets genName >>= mapM mkNonEmpty
253 834bea99 Helga Velroyen
  -- generate a random list of networks (possibly with duplicate names)
254 834bea99 Helga Velroyen
  nets <- vectorOf num_nets genValidNetwork
255 834bea99 Helga Velroyen
  -- use unique names for the networks
256 834bea99 Helga Velroyen
  let nets_unique = map ( \(name, net) -> net { networkName = name } )
257 834bea99 Helga Velroyen
        (zip net_names nets)
258 834bea99 Helga Velroyen
      net_map = GenericContainer $ Map.fromList
259 834bea99 Helga Velroyen
        (map (\n -> (networkUuid n, n)) nets_unique)
260 834bea99 Helga Velroyen
      new_cfg = old_cfg { configNetworks = net_map }
261 834bea99 Helga Velroyen
  return new_cfg
262 834bea99 Helga Velroyen
263 8d2b6a12 Iustin Pop
-- * Test properties
264 8d2b6a12 Iustin Pop
265 e5a29b6c Iustin Pop
-- | Tests that fillDict behaves correctly
266 20bc5360 Iustin Pop
prop_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
267 20bc5360 Iustin Pop
prop_fillDict defaults custom =
268 e5a29b6c Iustin Pop
  let d_map = Map.fromList defaults
269 e5a29b6c Iustin Pop
      d_keys = map fst defaults
270 e5a29b6c Iustin Pop
      c_map = Map.fromList custom
271 e5a29b6c Iustin Pop
      c_keys = map fst custom
272 942a9a6a Iustin Pop
  in conjoin [ printTestCase "Empty custom filling"
273 942a9a6a Iustin Pop
               (fillDict d_map Map.empty [] == d_map)
274 942a9a6a Iustin Pop
             , printTestCase "Empty defaults filling"
275 942a9a6a Iustin Pop
               (fillDict Map.empty c_map [] == c_map)
276 942a9a6a Iustin Pop
             , printTestCase "Delete all keys"
277 942a9a6a Iustin Pop
               (fillDict d_map c_map (d_keys++c_keys) == Map.empty)
278 942a9a6a Iustin Pop
             ]
279 8d2b6a12 Iustin Pop
280 8d2b6a12 Iustin Pop
-- | Test that the serialisation of 'DiskLogicalId', which is
281 8d2b6a12 Iustin Pop
-- implemented manually, is idempotent. Since we don't have a
282 8d2b6a12 Iustin Pop
-- standalone JSON instance for DiskLogicalId (it's a data type that
283 8d2b6a12 Iustin Pop
-- expands over two fields in a JSObject), we test this by actially
284 8d2b6a12 Iustin Pop
-- testing entire Disk serialisations. So this tests two things at
285 8d2b6a12 Iustin Pop
-- once, basically.
286 8d2b6a12 Iustin Pop
prop_Disk_serialisation :: Disk -> Property
287 63b068c1 Iustin Pop
prop_Disk_serialisation = testSerialisation
288 8d2b6a12 Iustin Pop
289 8d2b6a12 Iustin Pop
-- | Check that node serialisation is idempotent.
290 8d2b6a12 Iustin Pop
prop_Node_serialisation :: Node -> Property
291 63b068c1 Iustin Pop
prop_Node_serialisation = testSerialisation
292 e5a29b6c Iustin Pop
293 ce93b4a0 Iustin Pop
-- | Check that instance serialisation is idempotent.
294 ce93b4a0 Iustin Pop
prop_Inst_serialisation :: Instance -> Property
295 ce93b4a0 Iustin Pop
prop_Inst_serialisation = testSerialisation
296 ce93b4a0 Iustin Pop
297 76a0266e Helga Velroyen
-- | Check that network serialisation is idempotent.
298 76a0266e Helga Velroyen
prop_Network_serialisation :: Network -> Property
299 76a0266e Helga Velroyen
prop_Network_serialisation = testSerialisation
300 76a0266e Helga Velroyen
301 9924d61e Iustin Pop
-- | Check config serialisation.
302 9924d61e Iustin Pop
prop_Config_serialisation :: Property
303 9924d61e Iustin Pop
prop_Config_serialisation =
304 c3a8e06d Iustin Pop
  forAll (choose (0, maxNodes `div` 4) >>= genEmptyCluster) testSerialisation
305 9924d61e Iustin Pop
306 0b288282 Helga Velroyen
-- | Custom HUnit test to check the correspondence between Haskell-generated
307 0b288282 Helga Velroyen
-- networks and their Python decoded, validated and re-encoded version.
308 0b288282 Helga Velroyen
-- For the technical background of this unit test, check the documentation
309 83846468 Iustin Pop
-- of "case_py_compat_types" of test/hs/Test/Ganeti/Opcodes.hs
310 b1b4a26b Iustin Pop
casePyCompatNetworks :: HUnit.Assertion
311 b1b4a26b Iustin Pop
casePyCompatNetworks = do
312 0b288282 Helga Velroyen
  let num_networks = 500::Int
313 72747d91 Iustin Pop
  networks <- genSample (vectorOf num_networks genValidNetwork)
314 72747d91 Iustin Pop
  let networks_with_properties = map getNetworkProperties networks
315 0b288282 Helga Velroyen
      serialized = J.encode networks
316 0b288282 Helga Velroyen
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
317 0b288282 Helga Velroyen
  mapM_ (\net -> when (any (not . isAscii) (J.encode net)) .
318 0b288282 Helga Velroyen
                 HUnit.assertFailure $
319 0b288282 Helga Velroyen
                 "Network has non-ASCII fields: " ++ show net
320 0b288282 Helga Velroyen
        ) networks
321 0b288282 Helga Velroyen
  py_stdout <-
322 0b288282 Helga Velroyen
    runPython "from ganeti import network\n\
323 0b288282 Helga Velroyen
              \from ganeti import objects\n\
324 0b288282 Helga Velroyen
              \from ganeti import serializer\n\
325 0b288282 Helga Velroyen
              \import sys\n\
326 0b288282 Helga Velroyen
              \net_data = serializer.Load(sys.stdin.read())\n\
327 0b288282 Helga Velroyen
              \decoded = [objects.Network.FromDict(n) for n in net_data]\n\
328 0b288282 Helga Velroyen
              \encoded = []\n\
329 0b288282 Helga Velroyen
              \for net in decoded:\n\
330 0b288282 Helga Velroyen
              \  a = network.AddressPool(net)\n\
331 0b288282 Helga Velroyen
              \  encoded.append((a.GetFreeCount(), a.GetReservedCount(), \\\n\
332 0b288282 Helga Velroyen
              \    net.ToDict()))\n\
333 0b288282 Helga Velroyen
              \print serializer.Dump(encoded)" serialized
334 0b288282 Helga Velroyen
    >>= checkPythonResult
335 0b288282 Helga Velroyen
  let deserialised = J.decode py_stdout::J.Result [(Int, Int, Network)]
336 0b288282 Helga Velroyen
  decoded <- case deserialised of
337 0b288282 Helga Velroyen
               J.Ok ops -> return ops
338 0b288282 Helga Velroyen
               J.Error msg ->
339 0b288282 Helga Velroyen
                 HUnit.assertFailure ("Unable to decode networks: " ++ msg)
340 0b288282 Helga Velroyen
                 -- this already raised an expection, but we need it
341 0b288282 Helga Velroyen
                 -- for proper types
342 0b288282 Helga Velroyen
                 >> fail "Unable to decode networks"
343 0b288282 Helga Velroyen
  HUnit.assertEqual "Mismatch in number of returned networks"
344 0b288282 Helga Velroyen
    (length decoded) (length networks_with_properties)
345 0b288282 Helga Velroyen
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
346 0b288282 Helga Velroyen
        ) $ zip decoded networks_with_properties
347 0b288282 Helga Velroyen
348 0b288282 Helga Velroyen
-- | Creates a tuple of the given network combined with some of its properties
349 0b288282 Helga Velroyen
-- to be compared against the same properties generated by the python code.
350 0b288282 Helga Velroyen
getNetworkProperties :: Network -> (Int, Int, Network)
351 0b288282 Helga Velroyen
getNetworkProperties net =
352 0b288282 Helga Velroyen
  let maybePool = createAddressPool net
353 0b288282 Helga Velroyen
  in  case maybePool of
354 0b288282 Helga Velroyen
           (Just pool) -> (getFreeCount pool, getReservedCount pool, net)
355 0b288282 Helga Velroyen
           Nothing -> (-1, -1, net)
356 0b288282 Helga Velroyen
357 5b48df93 Helga Velroyen
-- | Tests the compatibility between Haskell-serialized node groups and their
358 5b48df93 Helga Velroyen
-- python-decoded and encoded version.
359 b1b4a26b Iustin Pop
casePyCompatNodegroups :: HUnit.Assertion
360 b1b4a26b Iustin Pop
casePyCompatNodegroups = do
361 5b48df93 Helga Velroyen
  let num_groups = 500::Int
362 72747d91 Iustin Pop
  groups <- genSample (vectorOf num_groups genNodeGroup)
363 72747d91 Iustin Pop
  let serialized = J.encode groups
364 5b48df93 Helga Velroyen
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
365 5b48df93 Helga Velroyen
  mapM_ (\group -> when (any (not . isAscii) (J.encode group)) .
366 5b48df93 Helga Velroyen
                 HUnit.assertFailure $
367 5b48df93 Helga Velroyen
                 "Node group has non-ASCII fields: " ++ show group
368 5b48df93 Helga Velroyen
        ) groups
369 5b48df93 Helga Velroyen
  py_stdout <-
370 5b48df93 Helga Velroyen
    runPython "from ganeti import objects\n\
371 5b48df93 Helga Velroyen
              \from ganeti import serializer\n\
372 5b48df93 Helga Velroyen
              \import sys\n\
373 5b48df93 Helga Velroyen
              \group_data = serializer.Load(sys.stdin.read())\n\
374 5b48df93 Helga Velroyen
              \decoded = [objects.NodeGroup.FromDict(g) for g in group_data]\n\
375 5b48df93 Helga Velroyen
              \encoded = [g.ToDict() for g in decoded]\n\
376 5b48df93 Helga Velroyen
              \print serializer.Dump(encoded)" serialized
377 5b48df93 Helga Velroyen
    >>= checkPythonResult
378 5b48df93 Helga Velroyen
  let deserialised = J.decode py_stdout::J.Result [NodeGroup]
379 5b48df93 Helga Velroyen
  decoded <- case deserialised of
380 5b48df93 Helga Velroyen
               J.Ok ops -> return ops
381 5b48df93 Helga Velroyen
               J.Error msg ->
382 5b48df93 Helga Velroyen
                 HUnit.assertFailure ("Unable to decode node groups: " ++ msg)
383 5b48df93 Helga Velroyen
                 -- this already raised an expection, but we need it
384 5b48df93 Helga Velroyen
                 -- for proper types
385 5b48df93 Helga Velroyen
                 >> fail "Unable to decode node groups"
386 5b48df93 Helga Velroyen
  HUnit.assertEqual "Mismatch in number of returned node groups"
387 5b48df93 Helga Velroyen
    (length decoded) (length groups)
388 5b48df93 Helga Velroyen
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
389 5b48df93 Helga Velroyen
        ) $ zip decoded groups
390 5b48df93 Helga Velroyen
391 5b48df93 Helga Velroyen
-- | Generates a node group with up to 3 networks.
392 5b48df93 Helga Velroyen
-- | FIXME: This generates still somewhat completely random data, without normal
393 5b48df93 Helga Velroyen
-- validation rules.
394 5b48df93 Helga Velroyen
genNodeGroup :: Gen NodeGroup
395 5b48df93 Helga Velroyen
genNodeGroup = do
396 5b48df93 Helga Velroyen
  name <- genFQDN
397 5b48df93 Helga Velroyen
  members <- pure []
398 5b48df93 Helga Velroyen
  ndparams <- arbitrary
399 5b48df93 Helga Velroyen
  alloc_policy <- arbitrary
400 5b48df93 Helga Velroyen
  ipolicy <- arbitrary
401 5b48df93 Helga Velroyen
  diskparams <- pure (GenericContainer Map.empty)
402 5b48df93 Helga Velroyen
  num_networks <- choose (0, 3)
403 da1dcce1 Helga Velroyen
  net_uuid_list <- vectorOf num_networks (arbitrary::Gen String)
404 2f3a3365 Helga Velroyen
  nic_param_list <- vectorOf num_networks (arbitrary::Gen PartialNicParams)
405 da1dcce1 Helga Velroyen
  net_map <- pure (GenericContainer . Map.fromList $
406 da1dcce1 Helga Velroyen
    zip net_uuid_list nic_param_list)
407 5b48df93 Helga Velroyen
  -- timestamp fields
408 5b48df93 Helga Velroyen
  ctime <- arbitrary
409 5b48df93 Helga Velroyen
  mtime <- arbitrary
410 e7124835 Iustin Pop
  uuid <- genFQDN `suchThat` (/= name)
411 5b48df93 Helga Velroyen
  serial <- arbitrary
412 5b48df93 Helga Velroyen
  tags <- Set.fromList <$> genTags
413 5b48df93 Helga Velroyen
  let group = NodeGroup name members ndparams alloc_policy ipolicy diskparams
414 da1dcce1 Helga Velroyen
              net_map ctime mtime uuid serial tags
415 5b48df93 Helga Velroyen
  return group
416 5b48df93 Helga Velroyen
417 5b48df93 Helga Velroyen
instance Arbitrary NodeGroup where
418 5b48df93 Helga Velroyen
  arbitrary = genNodeGroup
419 5b48df93 Helga Velroyen
420 3a991f2d Iustin Pop
$(genArbitrary ''Ip4Address)
421 3a991f2d Iustin Pop
422 3a991f2d Iustin Pop
$(genArbitrary ''Ip4Network)
423 3a991f2d Iustin Pop
424 3a991f2d Iustin Pop
-- | Helper to compute absolute value of an IPv4 address.
425 3a991f2d Iustin Pop
ip4AddrValue :: Ip4Address -> Integer
426 3a991f2d Iustin Pop
ip4AddrValue (Ip4Address a b c d) =
427 3a991f2d Iustin Pop
  fromIntegral a * (2^(24::Integer)) +
428 3a991f2d Iustin Pop
  fromIntegral b * (2^(16::Integer)) +
429 3a991f2d Iustin Pop
  fromIntegral c * (2^(8::Integer)) + fromIntegral d
430 3a991f2d Iustin Pop
431 3a991f2d Iustin Pop
-- | Tests that any difference between IPv4 consecutive addresses is 1.
432 3a991f2d Iustin Pop
prop_nextIp4Address :: Ip4Address -> Property
433 3a991f2d Iustin Pop
prop_nextIp4Address ip4 =
434 3a991f2d Iustin Pop
  ip4AddrValue (nextIp4Address ip4) ==? ip4AddrValue ip4 + 1
435 3a991f2d Iustin Pop
436 3a991f2d Iustin Pop
-- | IsString instance for 'Ip4Address', to help write the tests.
437 3a991f2d Iustin Pop
instance IsString Ip4Address where
438 3a991f2d Iustin Pop
  fromString s =
439 3a991f2d Iustin Pop
    fromMaybe (error $ "Failed to parse address from " ++ s) (readIp4Address s)
440 3a991f2d Iustin Pop
441 3a991f2d Iustin Pop
-- | Tests a few simple cases of IPv4 next address.
442 3a991f2d Iustin Pop
caseNextIp4Address :: HUnit.Assertion
443 3a991f2d Iustin Pop
caseNextIp4Address = do
444 3a991f2d Iustin Pop
  HUnit.assertEqual "" "0.0.0.1" $ nextIp4Address "0.0.0.0"
445 3a991f2d Iustin Pop
  HUnit.assertEqual "" "0.0.0.0" $ nextIp4Address "255.255.255.255"
446 3a991f2d Iustin Pop
  HUnit.assertEqual "" "1.2.3.5" $ nextIp4Address "1.2.3.4"
447 3a991f2d Iustin Pop
  HUnit.assertEqual "" "1.3.0.0" $ nextIp4Address "1.2.255.255"
448 3a991f2d Iustin Pop
  HUnit.assertEqual "" "1.2.255.63" $ nextIp4Address "1.2.255.62"
449 3a991f2d Iustin Pop
450 e5a29b6c Iustin Pop
testSuite "Objects"
451 20bc5360 Iustin Pop
  [ 'prop_fillDict
452 8d2b6a12 Iustin Pop
  , 'prop_Disk_serialisation
453 ce93b4a0 Iustin Pop
  , 'prop_Inst_serialisation
454 76a0266e Helga Velroyen
  , 'prop_Network_serialisation
455 8d2b6a12 Iustin Pop
  , 'prop_Node_serialisation
456 44be51aa Iustin Pop
  , 'prop_Config_serialisation
457 b1b4a26b Iustin Pop
  , 'casePyCompatNetworks
458 b1b4a26b Iustin Pop
  , 'casePyCompatNodegroups
459 3a991f2d Iustin Pop
  , 'prop_nextIp4Address
460 3a991f2d Iustin Pop
  , 'caseNextIp4Address
461 9924d61e Iustin Pop
  ]