Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (17.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, 2013 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.Node
30
  ( testHTools_Node
31
  , Node.Node(..)
32
  , setInstanceSmallerThanNode
33
  , genNode
34
  , genOnlineNode
35
  , genNodeList
36
  , genUniqueNodeList
37
  ) where
38

    
39
import Test.QuickCheck
40
import Test.HUnit
41

    
42
import Control.Monad
43
import qualified Data.Map as Map
44
import qualified Data.Graph as Graph
45
import Data.List
46

    
47
import Test.Ganeti.TestHelper
48
import Test.Ganeti.TestCommon
49
import Test.Ganeti.TestHTools
50
import Test.Ganeti.HTools.Instance ( genInstanceSmallerThanNode
51
                                   , genInstanceList
52
                                   , genInstanceOnNodeList)
53

    
54
import Ganeti.BasicTypes
55
import qualified Ganeti.HTools.Loader as Loader
56
import qualified Ganeti.HTools.Container as Container
57
import qualified Ganeti.HTools.Instance as Instance
58
import qualified Ganeti.HTools.Node as Node
59
import qualified Ganeti.HTools.Types as Types
60
import qualified Ganeti.HTools.Graph as HGraph
61

    
62
{-# ANN module "HLint: ignore Use camelCase" #-}
63

    
64
-- * Arbitrary instances
65

    
66
-- | Generates an arbitrary node based on sizing information.
67
genNode :: Maybe Int -- ^ Minimum node size in terms of units
68
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
69
                     -- just by the max... constants)
70
        -> Gen Node.Node
71
genNode min_multiplier max_multiplier = do
72
  let (base_mem, base_dsk, base_cpu, base_spindles) =
73
        case min_multiplier of
74
          Just mm -> (mm * Types.unitMem,
75
                      mm * Types.unitDsk,
76
                      mm * Types.unitCpu,
77
                      mm)
78
          Nothing -> (0, 0, 0, 0)
79
      (top_mem, top_dsk, top_cpu, top_spindles)  =
80
        case max_multiplier of
81
          Just mm -> (mm * Types.unitMem,
82
                      mm * Types.unitDsk,
83
                      mm * Types.unitCpu,
84
                      mm)
85
          Nothing -> (maxMem, maxDsk, maxCpu, maxSpindles)
86
  name  <- genFQDN
87
  mem_t <- choose (base_mem, top_mem)
88
  mem_f <- choose (base_mem, mem_t)
89
  mem_n <- choose (0, mem_t - mem_f)
90
  dsk_t <- choose (base_dsk, top_dsk)
91
  dsk_f <- choose (base_dsk, dsk_t)
92
  cpu_t <- choose (base_cpu, top_cpu)
93
  cpu_n <- choose (base_cpu, cpu_t)
94
  offl  <- arbitrary
95
  spindles <- choose (base_spindles, top_spindles)
96
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
97
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) cpu_n offl spindles
98
          0 0 False
99
      n' = Node.setPolicy nullIPolicy n
100
  return $ Node.buildPeers n' Container.empty
101

    
102
-- | Helper function to generate a sane node.
103
genOnlineNode :: Gen Node.Node
104
genOnlineNode =
105
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
106
                              not (Node.failN1 n) &&
107
                              Node.availDisk n > 0 &&
108
                              Node.availMem n > 0 &&
109
                              Node.availCpu n > 0 &&
110
                              Node.tSpindles n > 0)
111

    
112
-- | Generate a node with exclusive storage enabled.
113
genExclStorNode :: Gen Node.Node
114
genExclStorNode = do
115
  n <- genOnlineNode
116
  fs <- choose (Types.unitSpindle, Node.tSpindles n)
117
  let pd = fromIntegral fs / fromIntegral (Node.tSpindles n)::Double
118
  return n { Node.exclStorage = True
119
           , Node.fSpindles = fs
120
           , Node.pDsk = pd
121
           }
122

    
123
-- | Generate a node with exclusive storage possibly enabled.
124
genMaybeExclStorNode :: Gen Node.Node
125
genMaybeExclStorNode = oneof [genOnlineNode, genExclStorNode]
126

    
127
-- and a random node
128
instance Arbitrary Node.Node where
129
  arbitrary = genNode Nothing Nothing
130

    
131
-- | Node list generator.
132
-- Given a node generator, create a random length node list.  Note that "real"
133
-- clusters always have at least one node, so we don't generate empty node
134
-- lists here.
135
genNodeList :: Gen Node.Node -> Gen Node.List
136
genNodeList ngen = fmap (snd . Loader.assignIndices) names_nodes
137
    where names_nodes = (fmap . map) (\n -> (Node.name n, n)) $ listOf1 ngen
138

    
139
-- | Node list generator where node names are unique
140
genUniqueNodeList :: Gen Node.Node -> Gen (Node.List, Types.NameAssoc)
141
genUniqueNodeList ngen = (do
142
  nl <- genNodeList ngen
143
  let na = (fst . Loader.assignIndices) $
144
           map (\n -> (Node.name n, n)) (Container.elems nl)
145
  return (nl, na)) `suchThat`
146
    (\(nl, na) -> Container.size nl == Map.size na)
147

    
148
-- | Generate a node list, an instance list, and a node graph.
149
-- We choose instances with nodes contained in the node list.
150
genNodeGraph :: Gen (Maybe Graph.Graph, Node.List, Instance.List)
151
genNodeGraph = do
152
  nl <- genNodeList genOnlineNode `suchThat` ((2<=).Container.size)
153
  il <- genInstanceList (genInstanceOnNodeList nl)
154
  return (Node.mkNodeGraph nl il, nl, il)
155

    
156
-- * Test cases
157

    
158
prop_setAlias :: Node.Node -> String -> Bool
159
prop_setAlias node name =
160
  Node.name newnode == Node.name node &&
161
  Node.alias newnode == name
162
    where newnode = Node.setAlias node name
163

    
164
prop_setOffline :: Node.Node -> Bool -> Property
165
prop_setOffline node status =
166
  Node.offline newnode ==? status
167
    where newnode = Node.setOffline node status
168

    
169
prop_setXmem :: Node.Node -> Int -> Property
170
prop_setXmem node xm =
171
  Node.xMem newnode ==? xm
172
    where newnode = Node.setXmem node xm
173

    
174
prop_setMcpu :: Node.Node -> Double -> Property
175
prop_setMcpu node mc =
176
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
177
    where newnode = Node.setMcpu node mc
178

    
179
prop_setFmemGreater :: Node.Node -> Int -> Property
180
prop_setFmemGreater node new_mem =
181
  not (Node.failN1 node) && (Node.rMem node >= 0) &&
182
  (new_mem > Node.rMem node) ==>
183
  not (Node.failN1 (Node.setFmem node new_mem))
184

    
185
prop_setFmemExact :: Node.Node -> Property
186
prop_setFmemExact node =
187
  not (Node.failN1 node) && (Node.rMem node >= 0) ==>
188
  not (Node.failN1 (Node.setFmem node (Node.rMem node)))
189

    
190
-- Check if adding an instance that consumes exactly all reserved
191
-- memory does not raise an N+1 error
192
prop_addPri_NoN1Fail :: Property
193
prop_addPri_NoN1Fail =
194
  forAll genMaybeExclStorNode $ \node ->
195
  forAll (genInstanceSmallerThanNode node) $ \inst ->
196
  let inst' = inst { Instance.mem = Node.fMem node - Node.rMem node }
197
  in (Node.addPri node inst' /=? Bad Types.FailN1)
198

    
199
-- | Check that an instance add with too high memory or disk will be
200
-- rejected.
201
prop_addPriFM :: Node.Node -> Instance.Instance -> Property
202
prop_addPriFM node inst =
203
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
204
  not (Instance.isOffline inst) ==>
205
  (Node.addPri node inst'' ==? Bad Types.FailMem)
206
  where inst' = setInstanceSmallerThanNode node inst
207
        inst'' = inst' { Instance.mem = Instance.mem inst }
208

    
209
-- | Check that adding a primary instance with too much disk fails
210
-- with type FailDisk.
211
prop_addPriFD :: Node.Node -> Instance.Instance -> Property
212
prop_addPriFD node inst =
213
  forAll (elements Instance.localStorageTemplates) $ \dt ->
214
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
215
  let inst' = setInstanceSmallerThanNode node inst
216
      inst'' = inst' { Instance.dsk = Instance.dsk inst
217
                     , Instance.diskTemplate = dt }
218
  in (Node.addPri node inst'' ==? Bad Types.FailDisk)
219

    
220
-- | Check if an instance exceeds a spindles limit or has no spindles set.
221
hasInstTooManySpindles :: Instance.Instance -> Int -> Bool
222
hasInstTooManySpindles inst sp_lim =
223
  case Instance.getTotalSpindles inst of
224
    Just s -> s > sp_lim
225
    Nothing -> True
226

    
227
-- | Check that adding a primary instance with too many spindles fails
228
-- with type FailSpindles (when exclusive storage is enabled).
229
prop_addPriFS :: Instance.Instance -> Property
230
prop_addPriFS inst =
231
  forAll genExclStorNode $ \node ->
232
  forAll (elements Instance.localStorageTemplates) $ \dt ->
233
  hasInstTooManySpindles inst (Node.fSpindles node) &&
234
    not (Node.failN1 node) ==>
235
  let inst' = setInstanceSmallerThanNode node inst
236
      inst'' = inst' { Instance.disks = Instance.disks inst
237
                     , Instance.diskTemplate = dt }
238
  in (Node.addPri node inst'' ==? Bad Types.FailSpindles)
239

    
240
-- | Check that adding a primary instance with too many VCPUs fails
241
-- with type FailCPU.
242
prop_addPriFC :: Property
243
prop_addPriFC =
244
  forAll (choose (1, maxCpu)) $ \extra ->
245
  forAll genMaybeExclStorNode $ \node ->
246
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
247
  let inst' = setInstanceSmallerThanNode node inst
248
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
249
  in case Node.addPri node inst'' of
250
       Bad Types.FailCPU -> passTest
251
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
252

    
253
-- | Check that an instance add with too high memory or disk will be
254
-- rejected.
255
prop_addSec :: Node.Node -> Instance.Instance -> Int -> Property
256
prop_addSec node inst pdx =
257
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
258
    not (Instance.isOffline inst)) ||
259
   Instance.dsk inst >= Node.fDsk node ||
260
   (Node.exclStorage node &&
261
    hasInstTooManySpindles inst (Node.fSpindles node))) &&
262
  not (Node.failN1 node) ==>
263
      isBad (Node.addSec node inst pdx)
264

    
265
-- | Check that an offline instance with reasonable disk size but
266
-- extra mem/cpu can always be added.
267
prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
268
prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
269
  forAll genMaybeExclStorNode $ \node ->
270
  forAll (genInstanceSmallerThanNode node) $ \inst ->
271
  let inst' = inst { Instance.runSt = Types.StatusOffline
272
                   , Instance.mem = Node.availMem node + extra_mem
273
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
274
  in case Node.addPri node inst' of
275
       Ok _ -> passTest
276
       v -> failTest $ "Expected OpGood, but got: " ++ show v
277

    
278
-- | Check that an offline instance with reasonable disk size but
279
-- extra mem/cpu can always be added.
280
prop_addOfflineSec :: NonNegative Int -> NonNegative Int
281
                   -> Types.Ndx -> Property
282
prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
283
  forAll genMaybeExclStorNode $ \node ->
284
  forAll (genInstanceSmallerThanNode node) $ \inst ->
285
  let inst' = inst { Instance.runSt = Types.StatusOffline
286
                   , Instance.mem = Node.availMem node + extra_mem
287
                   , Instance.vcpus = Node.availCpu node + extra_cpu
288
                   , Instance.diskTemplate = Types.DTDrbd8 }
289
  in case Node.addSec node inst' pdx of
290
       Ok _ -> passTest
291
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
292

    
293
-- | Checks for memory reservation changes.
294
prop_rMem :: Instance.Instance -> Property
295
prop_rMem inst =
296
  not (Instance.isOffline inst) ==>
297
  forAll (genMaybeExclStorNode `suchThat` ((> Types.unitMem) . Node.fMem)) $
298
    \node ->
299
  -- ab = auto_balance, nb = non-auto_balance
300
  -- we use -1 as the primary node of the instance
301
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
302
                   , Instance.diskTemplate = Types.DTDrbd8 }
303
      inst_ab = setInstanceSmallerThanNode node inst'
304
      inst_nb = inst_ab { Instance.autoBalance = False }
305
      -- now we have the two instances, identical except the
306
      -- autoBalance attribute
307
      orig_rmem = Node.rMem node
308
      inst_idx = Instance.idx inst_ab
309
      node_add_ab = Node.addSec node inst_ab (-1)
310
      node_add_nb = Node.addSec node inst_nb (-1)
311
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
312
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
313
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
314
       (Ok a_ab, Ok a_nb,
315
        Ok d_ab, Ok d_nb) ->
316
         printTestCase "Consistency checks failed" $
317
           Node.rMem a_ab >  orig_rmem &&
318
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
319
           Node.rMem a_nb == orig_rmem &&
320
           Node.rMem d_ab == orig_rmem &&
321
           Node.rMem d_nb == orig_rmem &&
322
           -- this is not related to rMem, but as good a place to
323
           -- test as any
324
           inst_idx `elem` Node.sList a_ab &&
325
           inst_idx `notElem` Node.sList d_ab
326
       x -> failTest $ "Failed to add/remove instances: " ++ show x
327

    
328
-- | Check mdsk setting.
329
prop_setMdsk :: Node.Node -> SmallRatio -> Bool
330
prop_setMdsk node mx =
331
  Node.loDsk node' >= 0 &&
332
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
333
  Node.availDisk node' >= 0 &&
334
  Node.availDisk node' <= Node.fDsk node' &&
335
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
336
  Node.mDsk node' == mx'
337
    where node' = Node.setMdsk node mx'
338
          SmallRatio mx' = mx
339

    
340
-- Check tag maps
341
prop_tagMaps_idempotent :: Property
342
prop_tagMaps_idempotent =
343
  forAll genTags $ \tags ->
344
  Node.delTags (Node.addTags m tags) tags ==? m
345
    where m = Map.empty
346

    
347
prop_tagMaps_reject :: Property
348
prop_tagMaps_reject =
349
  forAll (genTags `suchThat` (not . null)) $ \tags ->
350
  let m = Node.addTags Map.empty tags
351
  in all (\t -> Node.rejectAddTags m [t]) tags
352

    
353
prop_showField :: Node.Node -> Property
354
prop_showField node =
355
  forAll (elements Node.defaultFields) $ \ field ->
356
  fst (Node.showHeader field) /= Types.unknownField &&
357
  Node.showField node field /= Types.unknownField
358

    
359
prop_computeGroups :: [Node.Node] -> Bool
360
prop_computeGroups nodes =
361
  let ng = Node.computeGroups nodes
362
      onlyuuid = map fst ng
363
  in length nodes == sum (map (length . snd) ng) &&
364
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
365
     length (nub onlyuuid) == length onlyuuid &&
366
     (null nodes || not (null ng))
367

    
368
-- Check idempotence of add/remove operations
369
prop_addPri_idempotent :: Property
370
prop_addPri_idempotent =
371
  forAll genMaybeExclStorNode $ \node ->
372
  forAll (genInstanceSmallerThanNode node) $ \inst ->
373
  case Node.addPri node inst of
374
    Ok node' -> Node.removePri node' inst ==? node
375
    _ -> failTest "Can't add instance"
376

    
377
prop_addSec_idempotent :: Property
378
prop_addSec_idempotent =
379
  forAll genMaybeExclStorNode $ \node ->
380
  forAll (genInstanceSmallerThanNode node) $ \inst ->
381
  let pdx = Node.idx node + 1
382
      inst' = Instance.setPri inst pdx
383
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
384
  in case Node.addSec node inst'' pdx of
385
       Ok node' -> Node.removeSec node' inst'' ==? node
386
       _ -> failTest "Can't add instance"
387

    
388
-- | Check that no graph is created on an empty node list.
389
case_emptyNodeList :: Assertion
390
case_emptyNodeList =
391
  assertEqual "" Nothing $ Node.mkNodeGraph emptynodes emptyinstances
392
    where emptynodes = Container.empty :: Node.List
393
          emptyinstances = Container.empty :: Instance.List
394

    
395
-- | Check that the number of vertices of a nodegraph is equal to the number of
396
-- nodes in the original node list.
397
prop_numVertices :: Property
398
prop_numVertices =
399
  forAll genNodeGraph $ \(graph, nl, _) ->
400
    (fmap numvertices graph ==? Just (Container.size nl))
401
    where numvertices = length . Graph.vertices
402

    
403
-- | Check that the number of edges of a nodegraph is equal to twice the number
404
-- of instances with secondary nodes in the original instance list.
405
prop_numEdges :: Property
406
prop_numEdges =
407
  forAll genNodeGraph $ \(graph, _, il) ->
408
    (fmap numedges graph ==? Just (numwithsec il * 2))
409
    where numedges = length . Graph.edges
410
          numwithsec = length . filter Instance.hasSecondary . Container.elems
411

    
412
-- | Check that a node graph is colorable.
413
prop_nodeGraphIsColorable :: Property
414
prop_nodeGraphIsColorable =
415
  forAll genNodeGraph $ \(graph, _, _) ->
416
    fmap HGraph.isColorable graph ==? Just True
417

    
418
-- | Check that each edge in a nodegraph is an instance.
419
prop_instanceIsEdge :: Property
420
prop_instanceIsEdge =
421
  forAll genNodeGraph $ \(graph, _, il) ->
422
    fmap (\g -> all (`isEdgeOn` g) (iwithsec il)) graph ==? Just True
423
    where i `isEdgeOn` g = iEdges i `intersect` Graph.edges g == iEdges i
424
          iEdges i = [ (Instance.pNode i, Instance.sNode i)
425
                     , (Instance.sNode i, Instance.pNode i)]
426
          iwithsec = filter Instance.hasSecondary . Container.elems
427

    
428
-- | Check that each instance in an edge in the resulting nodegraph.
429
prop_edgeIsInstance :: Property
430
prop_edgeIsInstance =
431
  forAll genNodeGraph $ \(graph, _, il) ->
432
    fmap (all (`isInstanceIn` il).Graph.edges) graph ==? Just True
433
      where e `isInstanceIn` il = any (`hasNodes` e) (Container.elems il)
434
            i `hasNodes` (v1,v2) =
435
              Instance.allNodes i `elem` permutations [v1,v2]
436

    
437
-- | List of tests for the Node module.
438
testSuite "HTools/Node"
439
            [ 'prop_setAlias
440
            , 'prop_setOffline
441
            , 'prop_setMcpu
442
            , 'prop_setFmemGreater
443
            , 'prop_setFmemExact
444
            , 'prop_setXmem
445
            , 'prop_addPriFM
446
            , 'prop_addPriFD
447
            , 'prop_addPriFS
448
            , 'prop_addPriFC
449
            , 'prop_addPri_NoN1Fail
450
            , 'prop_addSec
451
            , 'prop_addOfflinePri
452
            , 'prop_addOfflineSec
453
            , 'prop_rMem
454
            , 'prop_setMdsk
455
            , 'prop_tagMaps_idempotent
456
            , 'prop_tagMaps_reject
457
            , 'prop_showField
458
            , 'prop_computeGroups
459
            , 'prop_addPri_idempotent
460
            , 'prop_addSec_idempotent
461
            , 'case_emptyNodeList
462
            , 'prop_numVertices
463
            , 'prop_numEdges
464
            , 'prop_nodeGraphIsColorable
465
            , 'prop_edgeIsInstance
466
            , 'prop_instanceIsEdge
467
            ]