Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Container.hs @ 61899e64

History | View | Annotate | Download (3 kB)

1 e1ee7d5a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 e09c1fa0 Iustin Pop
module Test.Ganeti.HTools.Container (testHTools_Container) where
30 e1ee7d5a Iustin Pop
31 e1ee7d5a Iustin Pop
import Test.QuickCheck
32 e1ee7d5a Iustin Pop
33 e1ee7d5a Iustin Pop
import Data.Maybe
34 e1ee7d5a Iustin Pop
35 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
36 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
38 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Node (genNode)
39 e1ee7d5a Iustin Pop
40 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
41 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 e1ee7d5a Iustin Pop
43 e1ee7d5a Iustin Pop
-- we silence the following due to hlint bug fixed in later versions
44 20bc5360 Iustin Pop
{-# ANN prop_addTwo "HLint: ignore Avoid lambda" #-}
45 20bc5360 Iustin Pop
prop_addTwo :: [Container.Key] -> Int -> Int -> Bool
46 20bc5360 Iustin Pop
prop_addTwo cdata i1 i2 =
47 e1ee7d5a Iustin Pop
  fn i1 i2 cont == fn i2 i1 cont &&
48 e1ee7d5a Iustin Pop
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
49 e1ee7d5a Iustin Pop
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
50 e1ee7d5a Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
51 e1ee7d5a Iustin Pop
52 20bc5360 Iustin Pop
prop_nameOf :: Node.Node -> Property
53 20bc5360 Iustin Pop
prop_nameOf node =
54 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node 1
55 e1ee7d5a Iustin Pop
      fnode = head (Container.elems nl)
56 e1ee7d5a Iustin Pop
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
57 e1ee7d5a Iustin Pop
58 e1ee7d5a Iustin Pop
-- | We test that in a cluster, given a random node, we can find it by
59 e1ee7d5a Iustin Pop
-- its name and alias, as long as all names and aliases are unique,
60 e1ee7d5a Iustin Pop
-- and that we fail to find a non-existing name.
61 20bc5360 Iustin Pop
prop_findByName :: Property
62 20bc5360 Iustin Pop
prop_findByName =
63 e1ee7d5a Iustin Pop
  forAll (genNode (Just 1) Nothing) $ \node ->
64 e1ee7d5a Iustin Pop
  forAll (choose (1, 20)) $ \ cnt ->
65 e1ee7d5a Iustin Pop
  forAll (choose (0, cnt - 1)) $ \ fidx ->
66 e1ee7d5a Iustin Pop
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
67 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
68 e1ee7d5a Iustin Pop
  let names = zip (take cnt allnames) (drop cnt allnames)
69 e1ee7d5a Iustin Pop
      nl = makeSmallCluster node cnt
70 e1ee7d5a Iustin Pop
      nodes = Container.elems nl
71 e1ee7d5a Iustin Pop
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
72 e1ee7d5a Iustin Pop
                                             nn { Node.name = name,
73 e1ee7d5a Iustin Pop
                                                  Node.alias = alias }))
74 e1ee7d5a Iustin Pop
               $ zip names nodes
75 e1ee7d5a Iustin Pop
      nl' = Container.fromList nodes'
76 e1ee7d5a Iustin Pop
      target = snd (nodes' !! fidx)
77 942a9a6a Iustin Pop
  in conjoin
78 942a9a6a Iustin Pop
       [ Container.findByName nl' (Node.name target) ==? Just target
79 942a9a6a Iustin Pop
       , Container.findByName nl' (Node.alias target) ==? Just target
80 942a9a6a Iustin Pop
       , printTestCase "Found non-existing name"
81 942a9a6a Iustin Pop
         (isNothing (Container.findByName nl' othername))
82 942a9a6a Iustin Pop
       ]
83 e1ee7d5a Iustin Pop
84 e09c1fa0 Iustin Pop
testSuite "HTools/Container"
85 20bc5360 Iustin Pop
            [ 'prop_addTwo
86 20bc5360 Iustin Pop
            , 'prop_nameOf
87 20bc5360 Iustin Pop
            , 'prop_findByName
88 e1ee7d5a Iustin Pop
            ]