Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Cluster.hs @ 5b11f8db

History | View | Annotate | Download (15.4 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 _ -> False
138
       Types.Ok as ->
139
         case Cluster.asSolution as of
140
           Nothing -> False
141
           Just (xnl, xi, _, cv) ->
142
             let il' = Container.add (Instance.idx xi) xi il
143
                 tbl = Cluster.Table xnl il' cv []
144
             in not (canBalance tbl True True False)
145

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

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

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

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

    
238
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
239
-- we can also node-evacuate it.
240
prop_AllocEvacuate :: Property
241
prop_AllocEvacuate =
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
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
249
                              Cluster.tryNodeEvac defGroupList nl il mode
250
                                [Instance.idx inst']) .
251
                              evacModeOptions .
252
                              Instance.mirrorType $ inst'
253

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

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

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

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

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

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

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