Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Objects.hs @ 11e90588

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