Statistics
| Branch: | Tag: | Revision:

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

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