Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Cluster.hs @ 5a13489b

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
                                   , 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
  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 (genInstanceMaybeBiggerThanNode node) $ \inst ->
195
  let nl = makeSmallCluster node count
196
      il = Container.empty
197
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
198
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
199
  in case allocnodes >>= \allocnodes' ->
200
    Cluster.tieredAlloc nl il (Just 5) inst allocnodes' [] [] of
201
       Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
202
       Ok (_, nl', il', ixes, cstats) ->
203
         let (ai_alloc, ai_pool, ai_unav) =
204
               Cluster.computeAllocationDelta
205
                (Cluster.totalResources nl)
206
                (Cluster.totalResources nl')
207
             all_nodes fn = sum $ map fn (Container.elems nl)
208
             all_res fn = sum $ map fn [ai_alloc, ai_pool, ai_unav]
209
         in conjoin
210
            [ printTestCase "No instances allocated" $ not (null ixes)
211
            , IntMap.size il' ==? length ixes
212
            , length ixes     ==? length cstats
213
            , all_res Types.allocInfoVCpus ==? all_nodes Node.hiCpu
214
            , all_res Types.allocInfoNCpus ==? all_nodes Node.tCpu
215
            , all_res Types.allocInfoMem   ==? truncate (all_nodes Node.tMem)
216
            , all_res Types.allocInfoDisk  ==? truncate (all_nodes Node.tDsk)
217
            ]
218

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

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

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

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

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

    
318
-- | Check that allocating multiple instances on a cluster, then
319
-- adding an empty node, results in a valid rebalance.
320
prop_AllocBalance :: Property
321
prop_AllocBalance =
322
  forAll (genNode (Just 5) (Just 128)) $ \node ->
323
  forAll (choose (3, 5)) $ \count ->
324
  not (Node.offline node) && not (Node.failN1 node) ==>
325
  let nl = makeSmallCluster node count
326
      hnode = snd $ IntMap.findMax nl
327
      nl' = IntMap.deleteMax 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
       Bad msg -> failTest $ "Failed to allocate: " ++ msg
334
       Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
335
       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) =
347
        case Container.elems nl of
348
          [a, b, c] -> (a, b, c)
349
          l -> error $ "Invalid node list out of makeSmallCluster/3: " ++
350
               show l
351
      node3' = node3 { Node.group = 1 }
352
      nl' = Container.add (Node.idx node3') node3' nl
353
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
354
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
355
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
356
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
357
  in null (ccheck [(0, inst1)]) &&
358
     null (ccheck [(0, inst2)]) &&
359
     (not . null $ ccheck [(0, inst3)])
360

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

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

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

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