Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (3.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Test.Ganeti.HTools.Loader (testHTools_Loader) where
30

    
31
import Test.QuickCheck
32

    
33
import qualified Data.IntMap as IntMap
34
import qualified Data.Map as Map
35
import Data.List
36

    
37
import Test.Ganeti.TestHelper
38
import Test.Ganeti.TestCommon
39
import Test.Ganeti.HTools.Node ()
40

    
41
import qualified Ganeti.BasicTypes as BasicTypes
42
import qualified Ganeti.HTools.Container as Container
43
import qualified Ganeti.HTools.Loader as Loader
44
import qualified Ganeti.HTools.Node as Node
45

    
46
prop_lookupNode :: [(String, Int)] -> String -> String -> Property
47
prop_lookupNode ktn inst node =
48
  Loader.lookupNode nl inst node ==? Map.lookup node nl
49
    where nl = Map.fromList ktn
50

    
51
prop_lookupInstance :: [(String, Int)] -> String -> Property
52
prop_lookupInstance kti inst =
53
  Loader.lookupInstance il inst ==? Map.lookup inst il
54
    where il = Map.fromList kti
55

    
56
prop_assignIndices :: Property
57
prop_assignIndices =
58
  -- generate nodes with unique names
59
  forAll (arbitrary `suchThat`
60
          (\nodes ->
61
             let names = map Node.name nodes
62
             in length names == length (nub names))) $ \nodes ->
63
  let (nassoc, kt) =
64
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
65
  in Map.size nassoc == length nodes &&
66
     Container.size kt == length nodes &&
67
     (null nodes || maximum (IntMap.keys kt) == length nodes - 1)
68

    
69
-- | Checks that the number of primary instances recorded on the nodes
70
-- is zero.
71
prop_mergeData :: [Node.Node] -> Bool
72
prop_mergeData ns =
73
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
74
  in case Loader.mergeData [] [] [] []
75
         (Loader.emptyCluster {Loader.cdNodes = na}) of
76
    BasicTypes.Bad _ -> False
77
    BasicTypes.Ok (Loader.ClusterData _ nl il _ _) ->
78
      let nodes = Container.elems nl
79
          instances = Container.elems il
80
      in (sum . map (length . Node.pList)) nodes == 0 &&
81
         null instances
82

    
83
-- | Check that compareNameComponent on equal strings works.
84
prop_compareNameComponent_equal :: String -> Bool
85
prop_compareNameComponent_equal s =
86
  BasicTypes.compareNameComponent s s ==
87
    BasicTypes.LookupResult BasicTypes.ExactMatch s
88

    
89
-- | Check that compareNameComponent on prefix strings works.
90
prop_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
91
prop_compareNameComponent_prefix (NonEmpty s1) s2 =
92
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
93
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
94

    
95
testSuite "HTools/Loader"
96
            [ 'prop_lookupNode
97
            , 'prop_lookupInstance
98
            , 'prop_assignIndices
99
            , 'prop_mergeData
100
            , 'prop_compareNameComponent_equal
101
            , 'prop_compareNameComponent_prefix
102
            ]