Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (17.9 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 hiding (Result)
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 Ganeti.BasicTypes
44
import qualified Ganeti.HTools.Cluster as Cluster
45
import qualified Ganeti.HTools.Container as Container
46
import qualified Ganeti.HTools.Group as Group
47
import qualified Ganeti.HTools.IAlloc as IAlloc
48
import qualified Ganeti.HTools.Instance as Instance
49
import qualified Ganeti.HTools.Node as Node
50
import qualified Ganeti.HTools.Types as Types
51

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

    
54
-- * Helpers
55

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

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

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

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

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

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

    
101
-- * Test cases
102

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

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

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

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

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

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

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

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

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

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

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

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

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

    
370
-- | Helper function to check if we can allocate an instance on a
371
-- given node list. Successful allocation is denoted by 'Nothing',
372
-- otherwise the 'Just' value will contain the error message.
373
canAllocOn :: Node.List -> Int -> Instance.Instance -> Maybe String
374
canAllocOn nl reqnodes inst =
375
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
376
       Cluster.tryAlloc nl Container.empty inst of
377
       Bad msg -> Just $ "Can't allocate: " ++ msg
378
       Ok as ->
379
         case Cluster.asSolution as of
380
           Nothing -> Just $ "No allocation solution; failures: " ++
381
                      show (Cluster.collapseFailures $ Cluster.asFailures as)
382
           Just _ -> Nothing
383

    
384
-- | Checks that allocation obeys minimum and maximum instance
385
-- policies. The unittest generates a random node, duplicates it /count/
386
-- times, and generates a random instance that can be allocated on
387
-- this mini-cluster; it then checks that after applying a policy that
388
-- the instance doesn't fits, the allocation fails.
389
prop_AllocPolicy :: Property
390
prop_AllocPolicy =
391
  forAll genOnlineNode $ \node ->
392
  forAll (choose (5, 20)) $ \count ->
393
  forAll (genInstanceSmallerThanNode node) $ \inst ->
394
  forAll (arbitrary `suchThat` (isBad .
395
                                Instance.instMatchesPolicy inst)) $ \ipol ->
396
  let rqn = Instance.requiredNodes $ Instance.diskTemplate inst
397
      node' = Node.setPolicy ipol node
398
      nl = makeSmallCluster node' count
399
  in printTestCase "Allocation check:"
400
       (isNothing (canAllocOn (makeSmallCluster node count) rqn inst)) .&&.
401
     printTestCase "Policy failure check:" (isJust $ canAllocOn nl rqn inst)
402

    
403
testSuite "HTools/Cluster"
404
            [ 'prop_Score_Zero
405
            , 'prop_CStats_sane
406
            , 'prop_Alloc_sane
407
            , 'prop_IterateAlloc_sane
408
            , 'prop_CanTieredAlloc
409
            , 'prop_AllocRelocate
410
            , 'prop_AllocEvacuate
411
            , 'prop_AllocChangeGroup
412
            , 'prop_AllocBalance
413
            , 'prop_CheckConsistency
414
            , 'prop_SplitCluster
415
            , 'prop_AllocPolicy
416
            ]