Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (17.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.Cluster (testHTools_Cluster) where
30

    
31
import Test.QuickCheck
32

    
33
import qualified Data.IntMap as IntMap
34
import Data.Maybe
35

    
36
import Test.Ganeti.TestHelper
37
import Test.Ganeti.TestCommon
38
import Test.Ganeti.TestHTools
39
import Test.Ganeti.HTools.Instance ( genInstanceSmallerThanNode
40
                                   , genInstanceSmallerThan )
41
import Test.Ganeti.HTools.Node (genOnlineNode, genNode)
42

    
43
import qualified Ganeti.HTools.Cluster as Cluster
44
import qualified Ganeti.HTools.Container as Container
45
import qualified Ganeti.HTools.Group as Group
46
import qualified Ganeti.HTools.IAlloc as IAlloc
47
import qualified Ganeti.HTools.Instance as Instance
48
import qualified Ganeti.HTools.Node as Node
49
import qualified Ganeti.HTools.Types as Types
50

    
51
{-# ANN module "HLint: ignore Use camelCase" #-}
52

    
53
-- * Helpers
54

    
55
-- | Make a small cluster, both nodes and instances.
56
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
57
                      -> (Node.List, Instance.List, Instance.Instance)
58
makeSmallEmptyCluster node count inst =
59
  (makeSmallCluster node count, Container.empty,
60
   setInstanceSmallerThanNode node inst)
61

    
62
-- | Checks if a node is "big" enough.
63
isNodeBig :: Int -> Node.Node -> Bool
64
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
65
                      && Node.availMem node > size * Types.unitMem
66
                      && Node.availCpu node > size * Types.unitCpu
67

    
68
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
69
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
70

    
71
-- | Assigns a new fresh instance to a cluster; this is not
72
-- allocation, so no resource checks are done.
73
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
74
                  Types.Idx -> Types.Idx ->
75
                  (Node.List, Instance.List)
76
assignInstance nl il inst pdx sdx =
77
  let pnode = Container.find pdx nl
78
      snode = Container.find sdx nl
79
      maxiidx = if Container.null il
80
                  then 0
81
                  else fst (Container.findMax il) + 1
82
      inst' = inst { Instance.idx = maxiidx,
83
                     Instance.pNode = pdx, Instance.sNode = sdx }
84
      pnode' = Node.setPri pnode inst'
85
      snode' = Node.setSec snode inst'
86
      nl' = Container.addTwo pdx pnode' sdx snode' nl
87
      il' = Container.add maxiidx inst' il
88
  in (nl', il')
89

    
90
-- | Checks if an instance is mirrored.
91
isMirrored :: Instance.Instance -> Bool
92
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
93

    
94
-- | Returns the possible change node types for a disk template.
95
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
96
evacModeOptions Types.MirrorNone     = []
97
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
98
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
99

    
100
-- * Test cases
101

    
102
-- | Check that the cluster score is close to zero for a homogeneous
103
-- cluster.
104
prop_Score_Zero :: Node.Node -> Property
105
prop_Score_Zero node =
106
  forAll (choose (1, 1024)) $ \count ->
107
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
108
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
109
  let fn = Node.buildPeers node Container.empty
110
      nlst = replicate count fn
111
      score = Cluster.compCVNodes nlst
112
  -- we can't say == 0 here as the floating point errors accumulate;
113
  -- this should be much lower than the default score in CLI.hs
114
  in score <= 1e-12
115

    
116
-- | Check that cluster stats are sane.
117
prop_CStats_sane :: Property
118
prop_CStats_sane =
119
  forAll (choose (1, 1024)) $ \count ->
120
  forAll genOnlineNode $ \node ->
121
  let fn = Node.buildPeers node Container.empty
122
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
123
      nl = Container.fromList nlst
124
      cstats = Cluster.totalResources nl
125
  in Cluster.csAdsk cstats >= 0 &&
126
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
127

    
128
-- | Check that one instance is allocated correctly, without
129
-- rebalances needed.
130
prop_Alloc_sane :: Instance.Instance -> Property
131
prop_Alloc_sane inst =
132
  forAll (choose (5, 20)) $ \count ->
133
  forAll genOnlineNode $ \node ->
134
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
135
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
136
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
137
     Cluster.tryAlloc nl il inst' of
138
       Types.Bad msg -> failTest msg
139
       Types.Ok as ->
140
         case Cluster.asSolution as of
141
           Nothing -> failTest "Failed to allocate, empty solution"
142
           Just (xnl, xi, _, cv) ->
143
             let il' = Container.add (Instance.idx xi) xi il
144
                 tbl = Cluster.Table xnl il' cv []
145
             in printTestCase "Cluster can be balanced after allocation"
146
                  (not (canBalance tbl True True False)) .&&.
147
                printTestCase "Solution score differs from actual node list:"
148
                  (Cluster.compCV xnl ==? cv)
149

    
150
-- | Check that multiple instances can allocated correctly, without
151
-- rebalances needed.
152
prop_IterateAlloc_sane :: Instance.Instance -> Property
153
prop_IterateAlloc_sane inst =
154
  forAll (choose (5, 10)) $ \count ->
155
  forAll genOnlineNode $ \node ->
156
  forAll (choose (2, 5)) $ \limit ->
157
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
158
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
159
      allocnodes = Cluster.genAllocNodes defGroupList nl reqnodes True
160
  in case allocnodes >>= \allocnodes' ->
161
     Cluster.iterateAlloc nl il (Just limit) inst' allocnodes' [] [] of
162
       Types.Bad msg -> failTest msg
163
       Types.Ok (_, xnl, xil, _, _) ->
164
         let old_score = Cluster.compCV xnl
165
             tbl = Cluster.Table xnl xil old_score []
166
         in case Cluster.tryBalance tbl True True False 0 1e-4 of
167
              Nothing -> passTest
168
              Just (Cluster.Table ynl _ new_score plcs) ->
169
                -- note that with a "min_gain" of zero, sometime
170
                -- rounding errors can trigger a rebalance that
171
                -- improves the score by e.g. 2e-14; in order to
172
                -- prevent such no-real-change moves from happening,
173
                -- we check for a min-gain of 1e-9
174
                -- FIXME: correct rebalancing to not do no-ops
175
                printTestCase
176
                  ("Cluster can be balanced after allocation\n" ++
177
                   " old cluster (score " ++ show old_score ++
178
                   "):\n" ++ Cluster.printNodes xnl [] ++
179
                   " new cluster (score " ++ show new_score ++
180
                   "):\n" ++ Cluster.printNodes ynl [] ++
181
                   "placements:\n" ++ show plcs ++ "\nscore delta: " ++
182
                   show (old_score - new_score))
183
                  (old_score - new_score < 1e-9)
184

    
185
-- | Checks that on a 2-5 node cluster, we can allocate a random
186
-- instance spec via tiered allocation (whatever the original instance
187
-- spec), on either one or two nodes. Furthermore, we test that
188
-- computed allocation statistics are correct.
189
prop_CanTieredAlloc :: Property
190
prop_CanTieredAlloc =
191
  forAll (choose (2, 5)) $ \count ->
192
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
193
  forAll (genInstanceSmallerThan
194
            (Node.availMem  node + Types.unitMem * 2)
195
            (Node.availDisk node + Types.unitDsk * 3)
196
            (Node.availCpu  node + Types.unitCpu * 4)) $ \inst ->
197
  let nl = makeSmallCluster node count
198
      il = Container.empty
199
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
200
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
201
  in case allocnodes >>= \allocnodes' ->
202
    Cluster.tieredAlloc nl il (Just 5) inst allocnodes' [] [] of
203
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
204
       Types.Ok (_, nl', il', ixes, cstats) ->
205
         let (ai_alloc, ai_pool, ai_unav) =
206
               Cluster.computeAllocationDelta
207
                (Cluster.totalResources nl)
208
                (Cluster.totalResources nl')
209
             all_nodes fn = sum $ map fn (Container.elems nl)
210
             all_res fn = sum $ map fn [ai_alloc, ai_pool, ai_unav]
211
         in conjoin
212
            [ printTestCase "No instances allocated" $ not (null ixes)
213
            , IntMap.size il' ==? length ixes
214
            , length ixes     ==? length cstats
215
            , all_res Types.allocInfoVCpus ==? all_nodes Node.hiCpu
216
            , all_res Types.allocInfoNCpus ==? all_nodes Node.tCpu
217
            , all_res Types.allocInfoMem   ==? truncate (all_nodes Node.tMem)
218
            , all_res Types.allocInfoDisk  ==? truncate (all_nodes Node.tDsk)
219
            ]
220

    
221
-- | Helper function to create a cluster with the given range of nodes
222
-- and allocate an instance on it.
223
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
224
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
225
genClusterAlloc count node inst =
226
  let nl = makeSmallCluster node count
227
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
228
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
229
     Cluster.tryAlloc nl Container.empty inst of
230
       Types.Bad _ -> Types.Bad "Can't allocate"
231
       Types.Ok as ->
232
         case Cluster.asSolution as of
233
           Nothing -> Types.Bad "Empty solution?"
234
           Just (xnl, xi, _, _) ->
235
             let xil = Container.add (Instance.idx xi) xi Container.empty
236
             in Types.Ok (xnl, xil, xi)
237

    
238
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
239
-- we can also relocate it.
240
prop_AllocRelocate :: Property
241
prop_AllocRelocate =
242
  forAll (choose (4, 8)) $ \count ->
243
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
244
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
245
  case genClusterAlloc count node inst of
246
    Types.Bad msg -> failTest msg
247
    Types.Ok (nl, il, inst') ->
248
      case IAlloc.processRelocate defGroupList nl il
249
             (Instance.idx inst) 1
250
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
251
                 then Instance.sNode
252
                 else Instance.pNode) inst'] of
253
        Types.Ok _ -> passTest
254
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
255

    
256
-- | Helper property checker for the result of a nodeEvac or
257
-- changeGroup operation.
258
check_EvacMode :: Group.Group -> Instance.Instance
259
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
260
               -> Property
261
check_EvacMode grp inst result =
262
  case result of
263
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
264
    Types.Ok (_, _, es) ->
265
      let moved = Cluster.esMoved es
266
          failed = Cluster.esFailed es
267
          opcodes = not . null $ Cluster.esOpCodes es
268
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
269
         failmsg "'opcodes' is null" opcodes .&&.
270
         case moved of
271
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
272
                               .&&.
273
                               failmsg "wrong target group"
274
                                         (gdx == Group.idx grp)
275
           v -> failmsg  ("invalid solution: " ++ show v) False
276
  where failmsg :: String -> Bool -> Property
277
        failmsg msg = printTestCase ("Failed to evacuate: " ++ msg)
278
        idx = Instance.idx inst
279

    
280
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
281
-- we can also node-evacuate it.
282
prop_AllocEvacuate :: Property
283
prop_AllocEvacuate =
284
  forAll (choose (4, 8)) $ \count ->
285
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
286
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
287
  case genClusterAlloc count node inst of
288
    Types.Bad msg -> failTest msg
289
    Types.Ok (nl, il, inst') ->
290
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
291
                              Cluster.tryNodeEvac defGroupList nl il mode
292
                                [Instance.idx inst']) .
293
                              evacModeOptions .
294
                              Instance.mirrorType $ inst'
295

    
296
-- | Checks that on a 4-8 node cluster with two node groups, once we
297
-- allocate an instance on the first node group, we can also change
298
-- its group.
299
prop_AllocChangeGroup :: Property
300
prop_AllocChangeGroup =
301
  forAll (choose (4, 8)) $ \count ->
302
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
303
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
304
  case genClusterAlloc count node inst of
305
    Types.Bad msg -> failTest msg
306
    Types.Ok (nl, il, inst') ->
307
      -- we need to add a second node group and nodes to the cluster
308
      let nl2 = Container.elems $ makeSmallCluster node count
309
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
310
          maxndx = maximum . map Node.idx $ nl2
311
          nl3 = map (\n -> n { Node.group = Group.idx grp2
312
                             , Node.idx = Node.idx n + maxndx }) nl2
313
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
314
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
315
          nl' = IntMap.union nl nl4
316
      in check_EvacMode grp2 inst' $
317
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
318

    
319
-- | Check that allocating multiple instances on a cluster, then
320
-- adding an empty node, results in a valid rebalance.
321
prop_AllocBalance :: Property
322
prop_AllocBalance =
323
  forAll (genNode (Just 5) (Just 128)) $ \node ->
324
  forAll (choose (3, 5)) $ \count ->
325
  not (Node.offline node) && not (Node.failN1 node) ==>
326
  let nl = makeSmallCluster node count
327
      (hnode, nl') = IntMap.deleteFindMax nl
328
      il = Container.empty
329
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
330
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
331
  in case allocnodes >>= \allocnodes' ->
332
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
333
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
334
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
335
       Types.Ok (_, xnl, il', _, _) ->
336
         let ynl = Container.add (Node.idx hnode) hnode xnl
337
             cv = Cluster.compCV ynl
338
             tbl = Cluster.Table ynl il' cv []
339
         in printTestCase "Failed to rebalance" $
340
            canBalance tbl True True False
341

    
342
-- | Checks consistency.
343
prop_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
344
prop_CheckConsistency node inst =
345
  let nl = makeSmallCluster node 3
346
      [node1, node2, node3] = Container.elems nl
347
      node3' = node3 { Node.group = 1 }
348
      nl' = Container.add (Node.idx node3') node3' nl
349
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
350
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
351
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
352
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
353
  in null (ccheck [(0, inst1)]) &&
354
     null (ccheck [(0, inst2)]) &&
355
     (not . null $ ccheck [(0, inst3)])
356

    
357
-- | For now, we only test that we don't lose instances during the split.
358
prop_SplitCluster :: Node.Node -> Instance.Instance -> Property
359
prop_SplitCluster node inst =
360
  forAll (choose (0, 100)) $ \icnt ->
361
  let nl = makeSmallCluster node 2
362
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
363
                   (nl, Container.empty) [1..icnt]
364
      gni = Cluster.splitCluster nl' il'
365
  in sum (map (Container.size . snd . snd) gni) == icnt &&
366
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
367
                                 (Container.elems nl'')) gni
368

    
369
-- | Helper function to check if we can allocate an instance on a
370
-- given node list.
371
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
372
canAllocOn nl reqnodes inst =
373
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
374
       Cluster.tryAlloc nl Container.empty inst of
375
       Types.Bad _ -> False
376
       Types.Ok as ->
377
         case Cluster.asSolution as of
378
           Nothing -> False
379
           Just _ -> True
380

    
381
-- | Checks that allocation obeys minimum and maximum instance
382
-- policies. The unittest generates a random node, duplicates it /count/
383
-- times, and generates a random instance that can be allocated on
384
-- this mini-cluster; it then checks that after applying a policy that
385
-- the instance doesn't fits, the allocation fails.
386
prop_AllocPolicy :: Node.Node -> Property
387
prop_AllocPolicy node =
388
  -- rqn is the required nodes (1 or 2)
389
  forAll (choose (1, 2)) $ \rqn ->
390
  forAll (choose (5, 20)) $ \count ->
391
  forAll (arbitrary `suchThat` canAllocOn (makeSmallCluster node count) rqn)
392
         $ \inst ->
393
  forAll (arbitrary `suchThat` (isFailure .
394
                                Instance.instMatchesPolicy inst)) $ \ipol ->
395
  let node' = Node.setPolicy ipol node
396
      nl = makeSmallCluster node' count
397
  in not $ canAllocOn nl rqn inst
398

    
399
testSuite "HTools/Cluster"
400
            [ 'prop_Score_Zero
401
            , 'prop_CStats_sane
402
            , 'prop_Alloc_sane
403
            , 'prop_IterateAlloc_sane
404
            , 'prop_CanTieredAlloc
405
            , 'prop_AllocRelocate
406
            , 'prop_AllocEvacuate
407
            , 'prop_AllocChangeGroup
408
            , 'prop_AllocBalance
409
            , 'prop_CheckConsistency
410
            , 'prop_SplitCluster
411
            , 'prop_AllocPolicy
412
            ]