Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Loader.hs @ ef947a42

History | View | Annotate | Download (3.5 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
import System.Time (ClockTime(..))
37

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

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

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

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

    
57
prop_assignIndices :: Property
58
prop_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
     (null nodes || maximum (IntMap.keys kt) == length nodes - 1)
69

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

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

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

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