Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Cluster.hs @ c8c071cb

History | View | Annotate | Download (18 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
                                   , genInstanceMaybeBiggerThanNode )
41
import Test.Ganeti.HTools.Node (genOnlineNode, genNode)
42

    
43
import Ganeti.BasicTypes
44
import qualified Ganeti.HTools.Backend.IAlloc as IAlloc
45
import qualified Ganeti.HTools.Cluster as Cluster
46
import qualified Ganeti.HTools.Container as Container
47
import qualified Ganeti.HTools.Group as Group
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
     (Node.tSpindles node > 0) && (Node.tCpu node > 0)) ==>
111
  let fn = Node.buildPeers node Container.empty
112
      nlst = replicate count fn
113
      score = Cluster.compCVNodes nlst
114
  -- we can't say == 0 here as the floating point errors accumulate;
115
  -- this should be much lower than the default score in CLI.hs
116
  in score <= 1e-12
117

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

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

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

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

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

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

    
255
-- | Helper property checker for the result of a nodeEvac or
256
-- changeGroup operation.
257
check_EvacMode :: Group.Group -> Instance.Instance
258
               -> Result (Node.List, Instance.List, Cluster.EvacSolution)
259
               -> Property
260
check_EvacMode grp inst result =
261
  case result of
262
    Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
263
    Ok (_, _, es) ->
264
      let moved = Cluster.esMoved es
265
          failed = Cluster.esFailed es
266
          opcodes = not . null $ Cluster.esOpCodes es
267
      in conjoin
268
           [ failmsg ("'failed' not empty: " ++ show failed) (null failed)
269
           , failmsg "'opcodes' is null" opcodes
270
           , case moved of
271
               [(idx', gdx, _)] ->
272
                 failmsg "invalid instance moved" (idx == idx') .&&.
273
                 failmsg "wrong target group" (gdx == Group.idx grp)
274
               v -> failmsg  ("invalid solution: " ++ show v) False
275
           ]
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
    Bad msg -> failTest msg
289
    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
    Bad msg -> failTest msg
306
    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 = snd $ IntMap.findMax nl
328
      nl' = IntMap.deleteMax 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) =
348
        case Container.elems nl of
349
          [a, b, c] -> (a, b, c)
350
          l -> error $ "Invalid node list out of makeSmallCluster/3: " ++
351
               show l
352
      node3' = node3 { Node.group = 1 }
353
      nl' = Container.add (Node.idx node3') node3' nl
354
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
355
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
356
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
357
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
358
  in null (ccheck [(0, inst1)]) &&
359
     null (ccheck [(0, inst2)]) &&
360
     (not . null $ ccheck [(0, inst3)])
361

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

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

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

    
408
testSuite "HTools/Cluster"
409
            [ 'prop_Score_Zero
410
            , 'prop_CStats_sane
411
            , 'prop_Alloc_sane
412
            , 'prop_IterateAlloc_sane
413
            , 'prop_CanTieredAlloc
414
            , 'prop_AllocRelocate
415
            , 'prop_AllocEvacuate
416
            , 'prop_AllocChangeGroup
417
            , 'prop_AllocBalance
418
            , 'prop_CheckConsistency
419
            , 'prop_SplitCluster
420
            , 'prop_AllocPolicy
421
            ]