Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Node.hs @ 74ff6aed

History | View | Annotate | Download (17.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, 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
  offl  <- arbitrary
94
  spindles <- choose (base_spindles, top_spindles)
95
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
96
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl spindles
97
          0 0 False
98
      n' = Node.setPolicy nullIPolicy n
99
  return $ Node.buildPeers n' Container.empty
100

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

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

    
120
-- | Generate a node with exclusive storage possibly enabled.
121
genMaybeExclStorNode :: Gen Node.Node
122
genMaybeExclStorNode = oneof [genOnlineNode, genExclStorNode]
123

    
124
-- and a random node
125
instance Arbitrary Node.Node where
126
  arbitrary = genNode Nothing Nothing
127

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

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

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

    
153
-- * Test cases
154

    
155
prop_setAlias :: Node.Node -> String -> Bool
156
prop_setAlias node name =
157
  Node.name newnode == Node.name node &&
158
  Node.alias newnode == name
159
    where newnode = Node.setAlias node name
160

    
161
prop_setOffline :: Node.Node -> Bool -> Property
162
prop_setOffline node status =
163
  Node.offline newnode ==? status
164
    where newnode = Node.setOffline node status
165

    
166
prop_setXmem :: Node.Node -> Int -> Property
167
prop_setXmem node xm =
168
  Node.xMem newnode ==? xm
169
    where newnode = Node.setXmem node xm
170

    
171
prop_setMcpu :: Node.Node -> Double -> Property
172
prop_setMcpu node mc =
173
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
174
    where newnode = Node.setMcpu node mc
175

    
176
prop_setFmemGreater :: Node.Node -> Int -> Property
177
prop_setFmemGreater node new_mem =
178
  not (Node.failN1 node) && (Node.rMem node >= 0) &&
179
  (new_mem > Node.rMem node) ==>
180
  not (Node.failN1 (Node.setFmem node new_mem))
181

    
182
prop_setFmemExact :: Node.Node -> Property
183
prop_setFmemExact node =
184
  not (Node.failN1 node) && (Node.rMem node >= 0) ==>
185
  not (Node.failN1 (Node.setFmem node (Node.rMem node)))
186

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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