Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Loader.hs @ 8d2b6a12

History | View | Annotate | Download (3.5 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.Loader (testHTools_Loader) where
30 e1ee7d5a Iustin Pop
31 e1ee7d5a Iustin Pop
import Test.QuickCheck
32 e1ee7d5a Iustin Pop
33 e1ee7d5a Iustin Pop
import qualified Data.IntMap as IntMap
34 e1ee7d5a Iustin Pop
import qualified Data.Map as Map
35 e1ee7d5a Iustin Pop
import Data.List
36 e1ee7d5a Iustin Pop
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
39 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Node ()
40 e1ee7d5a Iustin Pop
41 e1ee7d5a Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
42 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
43 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
44 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
45 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
46 e1ee7d5a Iustin Pop
47 20bc5360 Iustin Pop
prop_lookupNode :: [(String, Int)] -> String -> String -> Property
48 20bc5360 Iustin Pop
prop_lookupNode ktn inst node =
49 e1ee7d5a Iustin Pop
  Loader.lookupNode nl inst node ==? Map.lookup node nl
50 e1ee7d5a Iustin Pop
    where nl = Map.fromList ktn
51 e1ee7d5a Iustin Pop
52 20bc5360 Iustin Pop
prop_lookupInstance :: [(String, Int)] -> String -> Property
53 20bc5360 Iustin Pop
prop_lookupInstance kti inst =
54 e1ee7d5a Iustin Pop
  Loader.lookupInstance il inst ==? Map.lookup inst il
55 e1ee7d5a Iustin Pop
    where il = Map.fromList kti
56 e1ee7d5a Iustin Pop
57 20bc5360 Iustin Pop
prop_assignIndices :: Property
58 20bc5360 Iustin Pop
prop_assignIndices =
59 e1ee7d5a Iustin Pop
  -- generate nodes with unique names
60 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat`
61 e1ee7d5a Iustin Pop
          (\nodes ->
62 e1ee7d5a Iustin Pop
             let names = map Node.name nodes
63 e1ee7d5a Iustin Pop
             in length names == length (nub names))) $ \nodes ->
64 e1ee7d5a Iustin Pop
  let (nassoc, kt) =
65 e1ee7d5a Iustin Pop
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
66 e1ee7d5a Iustin Pop
  in Map.size nassoc == length nodes &&
67 e1ee7d5a Iustin Pop
     Container.size kt == length nodes &&
68 e1ee7d5a Iustin Pop
     if not (null nodes)
69 e1ee7d5a Iustin Pop
       then maximum (IntMap.keys kt) == length nodes - 1
70 e1ee7d5a Iustin Pop
       else True
71 e1ee7d5a Iustin Pop
72 e1ee7d5a Iustin Pop
-- | Checks that the number of primary instances recorded on the nodes
73 e1ee7d5a Iustin Pop
-- is zero.
74 20bc5360 Iustin Pop
prop_mergeData :: [Node.Node] -> Bool
75 20bc5360 Iustin Pop
prop_mergeData ns =
76 e1ee7d5a Iustin Pop
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
77 e1ee7d5a Iustin Pop
  in case Loader.mergeData [] [] [] []
78 e1ee7d5a Iustin Pop
         (Loader.emptyCluster {Loader.cdNodes = na}) of
79 e1ee7d5a Iustin Pop
    Types.Bad _ -> False
80 e1ee7d5a Iustin Pop
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
81 e1ee7d5a Iustin Pop
      let nodes = Container.elems nl
82 e1ee7d5a Iustin Pop
          instances = Container.elems il
83 e1ee7d5a Iustin Pop
      in (sum . map (length . Node.pList)) nodes == 0 &&
84 e1ee7d5a Iustin Pop
         null instances
85 e1ee7d5a Iustin Pop
86 e1ee7d5a Iustin Pop
-- | Check that compareNameComponent on equal strings works.
87 20bc5360 Iustin Pop
prop_compareNameComponent_equal :: String -> Bool
88 20bc5360 Iustin Pop
prop_compareNameComponent_equal s =
89 e1ee7d5a Iustin Pop
  BasicTypes.compareNameComponent s s ==
90 e1ee7d5a Iustin Pop
    BasicTypes.LookupResult BasicTypes.ExactMatch s
91 e1ee7d5a Iustin Pop
92 e1ee7d5a Iustin Pop
-- | Check that compareNameComponent on prefix strings works.
93 20bc5360 Iustin Pop
prop_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
94 20bc5360 Iustin Pop
prop_compareNameComponent_prefix (NonEmpty s1) s2 =
95 e1ee7d5a Iustin Pop
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
96 e1ee7d5a Iustin Pop
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
97 e1ee7d5a Iustin Pop
98 e09c1fa0 Iustin Pop
testSuite "HTools/Loader"
99 20bc5360 Iustin Pop
            [ 'prop_lookupNode
100 20bc5360 Iustin Pop
            , 'prop_lookupInstance
101 20bc5360 Iustin Pop
            , 'prop_assignIndices
102 20bc5360 Iustin Pop
            , 'prop_mergeData
103 20bc5360 Iustin Pop
            , 'prop_compareNameComponent_equal
104 20bc5360 Iustin Pop
            , 'prop_compareNameComponent_prefix
105 e1ee7d5a Iustin Pop
            ]