Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Cluster.hs @ 650e5aa4

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

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

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

    
52
-- * Helpers
53

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

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

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

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

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

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

    
99
-- * Test cases
100

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

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

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

    
149
-- | Checks that on a 2-5 node cluster, we can allocate a random
150
-- instance spec via tiered allocation (whatever the original instance
151
-- spec), on either one or two nodes. Furthermore, we test that
152
-- computed allocation statistics are correct.
153
prop_CanTieredAlloc :: Instance.Instance -> Property
154
prop_CanTieredAlloc inst =
155
  forAll (choose (2, 5)) $ \count ->
156
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
157
  let nl = makeSmallCluster node count
158
      il = Container.empty
159
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
160
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
161
  in case allocnodes >>= \allocnodes' ->
162
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
163
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
164
       Types.Ok (_, nl', il', ixes, cstats) ->
165
         let (ai_alloc, ai_pool, ai_unav) =
166
               Cluster.computeAllocationDelta
167
                (Cluster.totalResources nl)
168
                (Cluster.totalResources nl')
169
             all_nodes = Container.elems nl
170
         in property (not (null ixes)) .&&.
171
            IntMap.size il' ==? length ixes .&&.
172
            length ixes ==? length cstats .&&.
173
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
174
              sum (map Node.hiCpu all_nodes) .&&.
175
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
176
              sum (map Node.tCpu all_nodes) .&&.
177
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
178
              truncate (sum (map Node.tMem all_nodes)) .&&.
179
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
180
              truncate (sum (map Node.tDsk all_nodes))
181

    
182
-- | Helper function to create a cluster with the given range of nodes
183
-- and allocate an instance on it.
184
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
185
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
186
genClusterAlloc count node inst =
187
  let nl = makeSmallCluster node count
188
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
189
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
190
     Cluster.tryAlloc nl Container.empty inst of
191
       Types.Bad _ -> Types.Bad "Can't allocate"
192
       Types.Ok as ->
193
         case Cluster.asSolution as of
194
           Nothing -> Types.Bad "Empty solution?"
195
           Just (xnl, xi, _, _) ->
196
             let xil = Container.add (Instance.idx xi) xi Container.empty
197
             in Types.Ok (xnl, xil, xi)
198

    
199
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
200
-- we can also relocate it.
201
prop_AllocRelocate :: Property
202
prop_AllocRelocate =
203
  forAll (choose (4, 8)) $ \count ->
204
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
205
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
206
  case genClusterAlloc count node inst of
207
    Types.Bad msg -> failTest msg
208
    Types.Ok (nl, il, inst') ->
209
      case IAlloc.processRelocate defGroupList nl il
210
             (Instance.idx inst) 1
211
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
212
                 then Instance.sNode
213
                 else Instance.pNode) inst'] of
214
        Types.Ok _ -> passTest
215
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
216

    
217
-- | Helper property checker for the result of a nodeEvac or
218
-- changeGroup operation.
219
check_EvacMode :: Group.Group -> Instance.Instance
220
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
221
               -> Property
222
check_EvacMode grp inst result =
223
  case result of
224
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
225
    Types.Ok (_, _, es) ->
226
      let moved = Cluster.esMoved es
227
          failed = Cluster.esFailed es
228
          opcodes = not . null $ Cluster.esOpCodes es
229
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
230
         failmsg "'opcodes' is null" opcodes .&&.
231
         case moved of
232
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
233
                               .&&.
234
                               failmsg "wrong target group"
235
                                         (gdx == Group.idx grp)
236
           v -> failmsg  ("invalid solution: " ++ show v) False
237
  where failmsg :: String -> Bool -> Property
238
        failmsg msg = printTestCase ("Failed to evacuate: " ++ msg)
239
        idx = Instance.idx inst
240

    
241
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
242
-- we can also node-evacuate it.
243
prop_AllocEvacuate :: Property
244
prop_AllocEvacuate =
245
  forAll (choose (4, 8)) $ \count ->
246
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
247
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
248
  case genClusterAlloc count node inst of
249
    Types.Bad msg -> failTest msg
250
    Types.Ok (nl, il, inst') ->
251
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
252
                              Cluster.tryNodeEvac defGroupList nl il mode
253
                                [Instance.idx inst']) .
254
                              evacModeOptions .
255
                              Instance.mirrorType $ inst'
256

    
257
-- | Checks that on a 4-8 node cluster with two node groups, once we
258
-- allocate an instance on the first node group, we can also change
259
-- its group.
260
prop_AllocChangeGroup :: Property
261
prop_AllocChangeGroup =
262
  forAll (choose (4, 8)) $ \count ->
263
  forAll (genOnlineNode `suchThat` isNodeBig 4) $ \node ->
264
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
265
  case genClusterAlloc count node inst of
266
    Types.Bad msg -> failTest msg
267
    Types.Ok (nl, il, inst') ->
268
      -- we need to add a second node group and nodes to the cluster
269
      let nl2 = Container.elems $ makeSmallCluster node count
270
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
271
          maxndx = maximum . map Node.idx $ nl2
272
          nl3 = map (\n -> n { Node.group = Group.idx grp2
273
                             , Node.idx = Node.idx n + maxndx }) nl2
274
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
275
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
276
          nl' = IntMap.union nl nl4
277
      in check_EvacMode grp2 inst' $
278
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
279

    
280
-- | Check that allocating multiple instances on a cluster, then
281
-- adding an empty node, results in a valid rebalance.
282
prop_AllocBalance :: Property
283
prop_AllocBalance =
284
  forAll (genNode (Just 5) (Just 128)) $ \node ->
285
  forAll (choose (3, 5)) $ \count ->
286
  not (Node.offline node) && not (Node.failN1 node) ==>
287
  let nl = makeSmallCluster node count
288
      (hnode, nl') = IntMap.deleteFindMax nl
289
      il = Container.empty
290
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
291
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
292
  in case allocnodes >>= \allocnodes' ->
293
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
294
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
295
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
296
       Types.Ok (_, xnl, il', _, _) ->
297
         let ynl = Container.add (Node.idx hnode) hnode xnl
298
             cv = Cluster.compCV ynl
299
             tbl = Cluster.Table ynl il' cv []
300
         in printTestCase "Failed to rebalance" $
301
            canBalance tbl True True False
302

    
303
-- | Checks consistency.
304
prop_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
305
prop_CheckConsistency node inst =
306
  let nl = makeSmallCluster node 3
307
      [node1, node2, node3] = Container.elems nl
308
      node3' = node3 { Node.group = 1 }
309
      nl' = Container.add (Node.idx node3') node3' nl
310
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
311
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
312
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
313
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
314
  in null (ccheck [(0, inst1)]) &&
315
     null (ccheck [(0, inst2)]) &&
316
     (not . null $ ccheck [(0, inst3)])
317

    
318
-- | For now, we only test that we don't lose instances during the split.
319
prop_SplitCluster :: Node.Node -> Instance.Instance -> Property
320
prop_SplitCluster node inst =
321
  forAll (choose (0, 100)) $ \icnt ->
322
  let nl = makeSmallCluster node 2
323
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
324
                   (nl, Container.empty) [1..icnt]
325
      gni = Cluster.splitCluster nl' il'
326
  in sum (map (Container.size . snd . snd) gni) == icnt &&
327
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
328
                                 (Container.elems nl'')) gni
329

    
330
-- | Helper function to check if we can allocate an instance on a
331
-- given node list.
332
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
333
canAllocOn nl reqnodes inst =
334
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
335
       Cluster.tryAlloc nl Container.empty inst of
336
       Types.Bad _ -> False
337
       Types.Ok as ->
338
         case Cluster.asSolution as of
339
           Nothing -> False
340
           Just _ -> True
341

    
342
-- | Checks that allocation obeys minimum and maximum instance
343
-- policies. The unittest generates a random node, duplicates it /count/
344
-- times, and generates a random instance that can be allocated on
345
-- this mini-cluster; it then checks that after applying a policy that
346
-- the instance doesn't fits, the allocation fails.
347
prop_AllocPolicy :: Node.Node -> Property
348
prop_AllocPolicy node =
349
  -- rqn is the required nodes (1 or 2)
350
  forAll (choose (1, 2)) $ \rqn ->
351
  forAll (choose (5, 20)) $ \count ->
352
  forAll (arbitrary `suchThat` canAllocOn (makeSmallCluster node count) rqn)
353
         $ \inst ->
354
  forAll (arbitrary `suchThat` (isFailure .
355
                                Instance.instMatchesPolicy inst)) $ \ipol ->
356
  let node' = Node.setPolicy ipol node
357
      nl = makeSmallCluster node' count
358
  in not $ canAllocOn nl rqn inst
359

    
360
testSuite "HTools/Cluster"
361
            [ 'prop_Score_Zero
362
            , 'prop_CStats_sane
363
            , 'prop_Alloc_sane
364
            , 'prop_CanTieredAlloc
365
            , 'prop_AllocRelocate
366
            , 'prop_AllocEvacuate
367
            , 'prop_AllocChangeGroup
368
            , 'prop_AllocBalance
369
            , 'prop_CheckConsistency
370
            , 'prop_SplitCluster
371
            , 'prop_AllocPolicy
372
            ]