Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 7af7da68

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