Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Node.hs @ 825f8cee

History | View | Annotate | Download (17.5 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
  let pd = fromIntegral fs / fromIntegral (Node.tSpindles n)::Double
117
  return n { Node.exclStorage = True
118
           , Node.fSpindles = fs
119
           , Node.pDsk = pd
120
           }
121

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

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

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

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

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

    
155
-- * Test cases
156

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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