Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Loader.hs @ e1ee7d5a

History | View | Annotate | Download (3.6 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 (testLoader) 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
import qualified Ganeti.HTools.Types as Types
46

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

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

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

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

    
86
-- | Check that compareNameComponent on equal strings works.
87
prop_Loader_compareNameComponent_equal :: String -> Bool
88
prop_Loader_compareNameComponent_equal s =
89
  BasicTypes.compareNameComponent s s ==
90
    BasicTypes.LookupResult BasicTypes.ExactMatch s
91

    
92
-- | Check that compareNameComponent on prefix strings works.
93
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
94
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
95
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
96
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
97

    
98
testSuite "Loader"
99
            [ 'prop_Loader_lookupNode
100
            , 'prop_Loader_lookupInstance
101
            , 'prop_Loader_assignIndices
102
            , 'prop_Loader_mergeData
103
            , 'prop_Loader_compareNameComponent_equal
104
            , 'prop_Loader_compareNameComponent_prefix
105
            ]