Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Cluster.hs @ e09c1fa0

History | View | Annotate | Download (15.4 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.Cluster (testHTools_Cluster) 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 Data.Maybe
35 e1ee7d5a Iustin Pop
36 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
39 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Instance (genInstanceSmallerThanNode)
40 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Node (genOnlineNode, genNode)
41 e1ee7d5a Iustin Pop
42 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
43 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
44 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Group as Group
45 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.IAlloc as IAlloc
46 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
47 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
48 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
49 e1ee7d5a Iustin Pop
50 e1ee7d5a Iustin Pop
-- * Helpers
51 e1ee7d5a Iustin Pop
52 e1ee7d5a Iustin Pop
-- | Make a small cluster, both nodes and instances.
53 e1ee7d5a Iustin Pop
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
54 e1ee7d5a Iustin Pop
                      -> (Node.List, Instance.List, Instance.Instance)
55 e1ee7d5a Iustin Pop
makeSmallEmptyCluster node count inst =
56 e1ee7d5a Iustin Pop
  (makeSmallCluster node count, Container.empty,
57 e1ee7d5a Iustin Pop
   setInstanceSmallerThanNode node inst)
58 e1ee7d5a Iustin Pop
59 e1ee7d5a Iustin Pop
-- | Checks if a node is "big" enough.
60 e1ee7d5a Iustin Pop
isNodeBig :: Int -> Node.Node -> Bool
61 e1ee7d5a Iustin Pop
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
62 e1ee7d5a Iustin Pop
                      && Node.availMem node > size * Types.unitMem
63 e1ee7d5a Iustin Pop
                      && Node.availCpu node > size * Types.unitCpu
64 e1ee7d5a Iustin Pop
65 e1ee7d5a Iustin Pop
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
66 e1ee7d5a Iustin Pop
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
67 e1ee7d5a Iustin Pop
68 e1ee7d5a Iustin Pop
-- | Assigns a new fresh instance to a cluster; this is not
69 e1ee7d5a Iustin Pop
-- allocation, so no resource checks are done.
70 e1ee7d5a Iustin Pop
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
71 e1ee7d5a Iustin Pop
                  Types.Idx -> Types.Idx ->
72 e1ee7d5a Iustin Pop
                  (Node.List, Instance.List)
73 e1ee7d5a Iustin Pop
assignInstance nl il inst pdx sdx =
74 e1ee7d5a Iustin Pop
  let pnode = Container.find pdx nl
75 e1ee7d5a Iustin Pop
      snode = Container.find sdx nl
76 e1ee7d5a Iustin Pop
      maxiidx = if Container.null il
77 e1ee7d5a Iustin Pop
                  then 0
78 e1ee7d5a Iustin Pop
                  else fst (Container.findMax il) + 1
79 e1ee7d5a Iustin Pop
      inst' = inst { Instance.idx = maxiidx,
80 e1ee7d5a Iustin Pop
                     Instance.pNode = pdx, Instance.sNode = sdx }
81 e1ee7d5a Iustin Pop
      pnode' = Node.setPri pnode inst'
82 e1ee7d5a Iustin Pop
      snode' = Node.setSec snode inst'
83 e1ee7d5a Iustin Pop
      nl' = Container.addTwo pdx pnode' sdx snode' nl
84 e1ee7d5a Iustin Pop
      il' = Container.add maxiidx inst' il
85 e1ee7d5a Iustin Pop
  in (nl', il')
86 e1ee7d5a Iustin Pop
87 e1ee7d5a Iustin Pop
-- | Checks if an instance is mirrored.
88 e1ee7d5a Iustin Pop
isMirrored :: Instance.Instance -> Bool
89 e1ee7d5a Iustin Pop
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
90 e1ee7d5a Iustin Pop
91 e1ee7d5a Iustin Pop
-- | Returns the possible change node types for a disk template.
92 e1ee7d5a Iustin Pop
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
93 e1ee7d5a Iustin Pop
evacModeOptions Types.MirrorNone     = []
94 e1ee7d5a Iustin Pop
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
95 e1ee7d5a Iustin Pop
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
96 e1ee7d5a Iustin Pop
97 e1ee7d5a Iustin Pop
-- * Test cases
98 e1ee7d5a Iustin Pop
99 e1ee7d5a Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous
100 e1ee7d5a Iustin Pop
-- cluster.
101 20bc5360 Iustin Pop
prop_Score_Zero :: Node.Node -> Property
102 20bc5360 Iustin Pop
prop_Score_Zero node =
103 e1ee7d5a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
104 e1ee7d5a Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
105 e1ee7d5a Iustin Pop
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
106 e1ee7d5a Iustin Pop
  let fn = Node.buildPeers node Container.empty
107 e1ee7d5a Iustin Pop
      nlst = replicate count fn
108 e1ee7d5a Iustin Pop
      score = Cluster.compCVNodes nlst
109 e1ee7d5a Iustin Pop
  -- we can't say == 0 here as the floating point errors accumulate;
110 e1ee7d5a Iustin Pop
  -- this should be much lower than the default score in CLI.hs
111 e1ee7d5a Iustin Pop
  in score <= 1e-12
112 e1ee7d5a Iustin Pop
113 e1ee7d5a Iustin Pop
-- | Check that cluster stats are sane.
114 20bc5360 Iustin Pop
prop_CStats_sane :: Property
115 20bc5360 Iustin Pop
prop_CStats_sane =
116 e1ee7d5a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
117 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
118 e1ee7d5a Iustin Pop
  let fn = Node.buildPeers node Container.empty
119 e1ee7d5a Iustin Pop
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
120 e1ee7d5a Iustin Pop
      nl = Container.fromList nlst
121 e1ee7d5a Iustin Pop
      cstats = Cluster.totalResources nl
122 e1ee7d5a Iustin Pop
  in Cluster.csAdsk cstats >= 0 &&
123 e1ee7d5a Iustin Pop
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
124 e1ee7d5a Iustin Pop
125 e1ee7d5a Iustin Pop
-- | Check that one instance is allocated correctly, without
126 e1ee7d5a Iustin Pop
-- rebalances needed.
127 20bc5360 Iustin Pop
prop_Alloc_sane :: Instance.Instance -> Property
128 20bc5360 Iustin Pop
prop_Alloc_sane inst =
129 e1ee7d5a Iustin Pop
  forAll (choose (5, 20)) $ \count ->
130 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
131 e1ee7d5a Iustin Pop
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
132 e1ee7d5a Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
133 e1ee7d5a Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
134 e1ee7d5a Iustin Pop
     Cluster.tryAlloc nl il inst' of
135 e1ee7d5a Iustin Pop
       Types.Bad _ -> False
136 e1ee7d5a Iustin Pop
       Types.Ok as ->
137 e1ee7d5a Iustin Pop
         case Cluster.asSolution as of
138 e1ee7d5a Iustin Pop
           Nothing -> False
139 e1ee7d5a Iustin Pop
           Just (xnl, xi, _, cv) ->
140 e1ee7d5a Iustin Pop
             let il' = Container.add (Instance.idx xi) xi il
141 e1ee7d5a Iustin Pop
                 tbl = Cluster.Table xnl il' cv []
142 e1ee7d5a Iustin Pop
             in not (canBalance tbl True True False)
143 e1ee7d5a Iustin Pop
144 e1ee7d5a Iustin Pop
-- | Checks that on a 2-5 node cluster, we can allocate a random
145 e1ee7d5a Iustin Pop
-- instance spec via tiered allocation (whatever the original instance
146 e1ee7d5a Iustin Pop
-- spec), on either one or two nodes. Furthermore, we test that
147 e1ee7d5a Iustin Pop
-- computed allocation statistics are correct.
148 20bc5360 Iustin Pop
prop_CanTieredAlloc :: Instance.Instance -> Property
149 20bc5360 Iustin Pop
prop_CanTieredAlloc inst =
150 e1ee7d5a Iustin Pop
  forAll (choose (2, 5)) $ \count ->
151 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
152 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node count
153 e1ee7d5a Iustin Pop
      il = Container.empty
154 e1ee7d5a Iustin Pop
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
155 e1ee7d5a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
156 e1ee7d5a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
157 e1ee7d5a Iustin Pop
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
158 e1ee7d5a Iustin Pop
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
159 e1ee7d5a Iustin Pop
       Types.Ok (_, nl', il', ixes, cstats) ->
160 e1ee7d5a Iustin Pop
         let (ai_alloc, ai_pool, ai_unav) =
161 e1ee7d5a Iustin Pop
               Cluster.computeAllocationDelta
162 e1ee7d5a Iustin Pop
                (Cluster.totalResources nl)
163 e1ee7d5a Iustin Pop
                (Cluster.totalResources nl')
164 e1ee7d5a Iustin Pop
             all_nodes = Container.elems nl
165 e1ee7d5a Iustin Pop
         in property (not (null ixes)) .&&.
166 e1ee7d5a Iustin Pop
            IntMap.size il' ==? length ixes .&&.
167 e1ee7d5a Iustin Pop
            length ixes ==? length cstats .&&.
168 e1ee7d5a Iustin Pop
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
169 e1ee7d5a Iustin Pop
              sum (map Node.hiCpu all_nodes) .&&.
170 e1ee7d5a Iustin Pop
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
171 e1ee7d5a Iustin Pop
              sum (map Node.tCpu all_nodes) .&&.
172 e1ee7d5a Iustin Pop
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
173 e1ee7d5a Iustin Pop
              truncate (sum (map Node.tMem all_nodes)) .&&.
174 e1ee7d5a Iustin Pop
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
175 e1ee7d5a Iustin Pop
              truncate (sum (map Node.tDsk all_nodes))
176 e1ee7d5a Iustin Pop
177 e1ee7d5a Iustin Pop
-- | Helper function to create a cluster with the given range of nodes
178 e1ee7d5a Iustin Pop
-- and allocate an instance on it.
179 e1ee7d5a Iustin Pop
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
180 e1ee7d5a Iustin Pop
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
181 e1ee7d5a Iustin Pop
genClusterAlloc count node inst =
182 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node count
183 e1ee7d5a Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
184 e1ee7d5a Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
185 e1ee7d5a Iustin Pop
     Cluster.tryAlloc nl Container.empty inst of
186 e1ee7d5a Iustin Pop
       Types.Bad _ -> Types.Bad "Can't allocate"
187 e1ee7d5a Iustin Pop
       Types.Ok as ->
188 e1ee7d5a Iustin Pop
         case Cluster.asSolution as of
189 e1ee7d5a Iustin Pop
           Nothing -> Types.Bad "Empty solution?"
190 e1ee7d5a Iustin Pop
           Just (xnl, xi, _, _) ->
191 e1ee7d5a Iustin Pop
             let xil = Container.add (Instance.idx xi) xi Container.empty
192 e1ee7d5a Iustin Pop
             in Types.Ok (xnl, xil, xi)
193 e1ee7d5a Iustin Pop
194 e1ee7d5a Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
195 e1ee7d5a Iustin Pop
-- we can also relocate it.
196 20bc5360 Iustin Pop
prop_AllocRelocate :: Property
197 20bc5360 Iustin Pop
prop_AllocRelocate =
198 e1ee7d5a Iustin Pop
  forAll (choose (4, 8)) $ \count ->
199 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
200 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
201 e1ee7d5a Iustin Pop
  case genClusterAlloc count node inst of
202 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest msg
203 e1ee7d5a Iustin Pop
    Types.Ok (nl, il, inst') ->
204 e1ee7d5a Iustin Pop
      case IAlloc.processRelocate defGroupList nl il
205 e1ee7d5a Iustin Pop
             (Instance.idx inst) 1
206 e1ee7d5a Iustin Pop
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
207 e1ee7d5a Iustin Pop
                 then Instance.sNode
208 e1ee7d5a Iustin Pop
                 else Instance.pNode) inst'] of
209 e1ee7d5a Iustin Pop
        Types.Ok _ -> property True
210 e1ee7d5a Iustin Pop
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
211 e1ee7d5a Iustin Pop
212 e1ee7d5a Iustin Pop
-- | Helper property checker for the result of a nodeEvac or
213 e1ee7d5a Iustin Pop
-- changeGroup operation.
214 e1ee7d5a Iustin Pop
check_EvacMode :: Group.Group -> Instance.Instance
215 e1ee7d5a Iustin Pop
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
216 e1ee7d5a Iustin Pop
               -> Property
217 e1ee7d5a Iustin Pop
check_EvacMode grp inst result =
218 e1ee7d5a Iustin Pop
  case result of
219 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
220 e1ee7d5a Iustin Pop
    Types.Ok (_, _, es) ->
221 e1ee7d5a Iustin Pop
      let moved = Cluster.esMoved es
222 e1ee7d5a Iustin Pop
          failed = Cluster.esFailed es
223 e1ee7d5a Iustin Pop
          opcodes = not . null $ Cluster.esOpCodes es
224 e1ee7d5a Iustin Pop
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
225 e1ee7d5a Iustin Pop
         failmsg "'opcodes' is null" opcodes .&&.
226 e1ee7d5a Iustin Pop
         case moved of
227 e1ee7d5a Iustin Pop
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
228 e1ee7d5a Iustin Pop
                               .&&.
229 e1ee7d5a Iustin Pop
                               failmsg "wrong target group"
230 e1ee7d5a Iustin Pop
                                         (gdx == Group.idx grp)
231 e1ee7d5a Iustin Pop
           v -> failmsg  ("invalid solution: " ++ show v) False
232 e1ee7d5a Iustin Pop
  where failmsg :: String -> Bool -> Property
233 e1ee7d5a Iustin Pop
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
234 e1ee7d5a Iustin Pop
        idx = Instance.idx inst
235 e1ee7d5a Iustin Pop
236 e1ee7d5a Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
237 e1ee7d5a Iustin Pop
-- we can also node-evacuate it.
238 20bc5360 Iustin Pop
prop_AllocEvacuate :: Property
239 20bc5360 Iustin Pop
prop_AllocEvacuate =
240 e1ee7d5a Iustin Pop
  forAll (choose (4, 8)) $ \count ->
241 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
242 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
243 e1ee7d5a Iustin Pop
  case genClusterAlloc count node inst of
244 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest msg
245 e1ee7d5a Iustin Pop
    Types.Ok (nl, il, inst') ->
246 e1ee7d5a Iustin Pop
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
247 e1ee7d5a Iustin Pop
                              Cluster.tryNodeEvac defGroupList nl il mode
248 e1ee7d5a Iustin Pop
                                [Instance.idx inst']) .
249 e1ee7d5a Iustin Pop
                              evacModeOptions .
250 e1ee7d5a Iustin Pop
                              Instance.mirrorType $ inst'
251 e1ee7d5a Iustin Pop
252 e1ee7d5a Iustin Pop
-- | Checks that on a 4-8 node cluster with two node groups, once we
253 e1ee7d5a Iustin Pop
-- allocate an instance on the first node group, we can also change
254 e1ee7d5a Iustin Pop
-- its group.
255 20bc5360 Iustin Pop
prop_AllocChangeGroup :: Property
256 20bc5360 Iustin Pop
prop_AllocChangeGroup =
257 e1ee7d5a Iustin Pop
  forAll (choose (4, 8)) $ \count ->
258 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
259 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
260 e1ee7d5a Iustin Pop
  case genClusterAlloc count node inst of
261 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest msg
262 e1ee7d5a Iustin Pop
    Types.Ok (nl, il, inst') ->
263 e1ee7d5a Iustin Pop
      -- we need to add a second node group and nodes to the cluster
264 e1ee7d5a Iustin Pop
      let nl2 = Container.elems $ makeSmallCluster node count
265 e1ee7d5a Iustin Pop
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
266 e1ee7d5a Iustin Pop
          maxndx = maximum . map Node.idx $ nl2
267 e1ee7d5a Iustin Pop
          nl3 = map (\n -> n { Node.group = Group.idx grp2
268 e1ee7d5a Iustin Pop
                             , Node.idx = Node.idx n + maxndx }) nl2
269 e1ee7d5a Iustin Pop
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
270 e1ee7d5a Iustin Pop
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
271 e1ee7d5a Iustin Pop
          nl' = IntMap.union nl nl4
272 e1ee7d5a Iustin Pop
      in check_EvacMode grp2 inst' $
273 e1ee7d5a Iustin Pop
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
274 e1ee7d5a Iustin Pop
275 e1ee7d5a Iustin Pop
-- | Check that allocating multiple instances on a cluster, then
276 e1ee7d5a Iustin Pop
-- adding an empty node, results in a valid rebalance.
277 20bc5360 Iustin Pop
prop_AllocBalance :: Property
278 20bc5360 Iustin Pop
prop_AllocBalance =
279 e1ee7d5a Iustin Pop
  forAll (genNode (Just 5) (Just 128)) $ \node ->
280 e1ee7d5a Iustin Pop
  forAll (choose (3, 5)) $ \count ->
281 e1ee7d5a Iustin Pop
  not (Node.offline node) && not (Node.failN1 node) ==>
282 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node count
283 e1ee7d5a Iustin Pop
      (hnode, nl') = IntMap.deleteFindMax nl
284 e1ee7d5a Iustin Pop
      il = Container.empty
285 e1ee7d5a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
286 e1ee7d5a Iustin Pop
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
287 e1ee7d5a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
288 e1ee7d5a Iustin Pop
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
289 e1ee7d5a Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
290 e1ee7d5a Iustin Pop
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
291 e1ee7d5a Iustin Pop
       Types.Ok (_, xnl, il', _, _) ->
292 e1ee7d5a Iustin Pop
         let ynl = Container.add (Node.idx hnode) hnode xnl
293 e1ee7d5a Iustin Pop
             cv = Cluster.compCV ynl
294 e1ee7d5a Iustin Pop
             tbl = Cluster.Table ynl il' cv []
295 e1ee7d5a Iustin Pop
         in printTestCase "Failed to rebalance" $
296 e1ee7d5a Iustin Pop
            canBalance tbl True True False
297 e1ee7d5a Iustin Pop
298 e1ee7d5a Iustin Pop
-- | Checks consistency.
299 20bc5360 Iustin Pop
prop_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
300 20bc5360 Iustin Pop
prop_CheckConsistency node inst =
301 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node 3
302 e1ee7d5a Iustin Pop
      [node1, node2, node3] = Container.elems nl
303 e1ee7d5a Iustin Pop
      node3' = node3 { Node.group = 1 }
304 e1ee7d5a Iustin Pop
      nl' = Container.add (Node.idx node3') node3' nl
305 e1ee7d5a Iustin Pop
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
306 e1ee7d5a Iustin Pop
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
307 e1ee7d5a Iustin Pop
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
308 e1ee7d5a Iustin Pop
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
309 e1ee7d5a Iustin Pop
  in null (ccheck [(0, inst1)]) &&
310 e1ee7d5a Iustin Pop
     null (ccheck [(0, inst2)]) &&
311 e1ee7d5a Iustin Pop
     (not . null $ ccheck [(0, inst3)])
312 e1ee7d5a Iustin Pop
313 e1ee7d5a Iustin Pop
-- | For now, we only test that we don't lose instances during the split.
314 20bc5360 Iustin Pop
prop_SplitCluster :: Node.Node -> Instance.Instance -> Property
315 20bc5360 Iustin Pop
prop_SplitCluster node inst =
316 e1ee7d5a Iustin Pop
  forAll (choose (0, 100)) $ \icnt ->
317 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node 2
318 e1ee7d5a Iustin Pop
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
319 e1ee7d5a Iustin Pop
                   (nl, Container.empty) [1..icnt]
320 e1ee7d5a Iustin Pop
      gni = Cluster.splitCluster nl' il'
321 e1ee7d5a Iustin Pop
  in sum (map (Container.size . snd . snd) gni) == icnt &&
322 e1ee7d5a Iustin Pop
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
323 e1ee7d5a Iustin Pop
                                 (Container.elems nl'')) gni
324 e1ee7d5a Iustin Pop
325 e1ee7d5a Iustin Pop
-- | Helper function to check if we can allocate an instance on a
326 e1ee7d5a Iustin Pop
-- given node list.
327 e1ee7d5a Iustin Pop
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
328 e1ee7d5a Iustin Pop
canAllocOn nl reqnodes inst =
329 e1ee7d5a Iustin Pop
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
330 e1ee7d5a Iustin Pop
       Cluster.tryAlloc nl (Container.empty) inst of
331 e1ee7d5a Iustin Pop
       Types.Bad _ -> False
332 e1ee7d5a Iustin Pop
       Types.Ok as ->
333 e1ee7d5a Iustin Pop
         case Cluster.asSolution as of
334 e1ee7d5a Iustin Pop
           Nothing -> False
335 e1ee7d5a Iustin Pop
           Just _ -> True
336 e1ee7d5a Iustin Pop
337 e1ee7d5a Iustin Pop
-- | Checks that allocation obeys minimum and maximum instance
338 e1ee7d5a Iustin Pop
-- policies. The unittest generates a random node, duplicates it /count/
339 e1ee7d5a Iustin Pop
-- times, and generates a random instance that can be allocated on
340 e1ee7d5a Iustin Pop
-- this mini-cluster; it then checks that after applying a policy that
341 e1ee7d5a Iustin Pop
-- the instance doesn't fits, the allocation fails.
342 20bc5360 Iustin Pop
prop_AllocPolicy :: Node.Node -> Property
343 20bc5360 Iustin Pop
prop_AllocPolicy node =
344 e1ee7d5a Iustin Pop
  -- rqn is the required nodes (1 or 2)
345 e1ee7d5a Iustin Pop
  forAll (choose (1, 2)) $ \rqn ->
346 e1ee7d5a Iustin Pop
  forAll (choose (5, 20)) $ \count ->
347 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
348 e1ee7d5a Iustin Pop
         $ \inst ->
349 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat` (isFailure .
350 e1ee7d5a Iustin Pop
                                Instance.instMatchesPolicy inst)) $ \ipol ->
351 e1ee7d5a Iustin Pop
  let node' = Node.setPolicy ipol node
352 e1ee7d5a Iustin Pop
      nl = makeSmallCluster node' count
353 e1ee7d5a Iustin Pop
  in not $ canAllocOn nl rqn inst
354 e1ee7d5a Iustin Pop
355 e09c1fa0 Iustin Pop
testSuite "HTools/Cluster"
356 20bc5360 Iustin Pop
            [ 'prop_Score_Zero
357 20bc5360 Iustin Pop
            , 'prop_CStats_sane
358 20bc5360 Iustin Pop
            , 'prop_Alloc_sane
359 20bc5360 Iustin Pop
            , 'prop_CanTieredAlloc
360 20bc5360 Iustin Pop
            , 'prop_AllocRelocate
361 20bc5360 Iustin Pop
            , 'prop_AllocEvacuate
362 20bc5360 Iustin Pop
            , 'prop_AllocChangeGroup
363 20bc5360 Iustin Pop
            , 'prop_AllocBalance
364 20bc5360 Iustin Pop
            , 'prop_CheckConsistency
365 20bc5360 Iustin Pop
            , 'prop_SplitCluster
366 20bc5360 Iustin Pop
            , 'prop_AllocPolicy
367 e1ee7d5a Iustin Pop
            ]