Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (15.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 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
  ) where
37

    
38
import Test.QuickCheck
39
import Test.HUnit
40

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

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

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

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

    
63
-- * Arbitrary instances
64

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

    
96
-- | Helper function to generate a sane node.
97
genOnlineNode :: Gen Node.Node
98
genOnlineNode =
99
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
100
                              not (Node.failN1 n) &&
101
                              Node.availDisk n > 0 &&
102
                              Node.availMem n > 0 &&
103
                              Node.availCpu n > 0)
104

    
105
-- and a random node
106
instance Arbitrary Node.Node where
107
  arbitrary = genNode Nothing Nothing
108

    
109
-- | Node list generator.
110
-- Given a node generator, create a random length node list.  Note that "real"
111
-- clusters always have at least one node, so we don't generate empty node
112
-- lists here.
113
genNodeList :: Gen Node.Node -> Gen Node.List
114
genNodeList ngen = fmap (snd . Loader.assignIndices) names_nodes
115
    where names_nodes = (fmap . map) (\n -> (Node.name n, n)) nodes
116
          nodes = listOf1 ngen `suchThat`
117
                  ((\ns -> ns == nub ns) . map Node.name)
118

    
119
-- | Generate a node list, an instance list, and a node graph.
120
-- We choose instances with nodes contained in the node list.
121
genNodeGraph :: Gen (Maybe Graph.Graph, Node.List, Instance.List)
122
genNodeGraph = do
123
  nl <- genNodeList genOnlineNode `suchThat` ((2<=).Container.size)
124
  il <- genInstanceList (genInstanceOnNodeList nl)
125
  return (Node.mkNodeGraph nl il, nl, il)
126

    
127
-- * Test cases
128

    
129
prop_setAlias :: Node.Node -> String -> Bool
130
prop_setAlias node name =
131
  Node.name newnode == Node.name node &&
132
  Node.alias newnode == name
133
    where newnode = Node.setAlias node name
134

    
135
prop_setOffline :: Node.Node -> Bool -> Property
136
prop_setOffline node status =
137
  Node.offline newnode ==? status
138
    where newnode = Node.setOffline node status
139

    
140
prop_setXmem :: Node.Node -> Int -> Property
141
prop_setXmem node xm =
142
  Node.xMem newnode ==? xm
143
    where newnode = Node.setXmem node xm
144

    
145
prop_setMcpu :: Node.Node -> Double -> Property
146
prop_setMcpu node mc =
147
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
148
    where newnode = Node.setMcpu node mc
149

    
150
prop_setFmemGreater :: Node.Node -> Int -> Property
151
prop_setFmemGreater node new_mem =
152
  not (Node.failN1 node) && (Node.rMem node >= 0) &&
153
  (new_mem > Node.rMem node) ==>
154
  not (Node.failN1 (Node.setFmem node new_mem))
155

    
156
prop_setFmemExact :: Node.Node -> Property
157
prop_setFmemExact node =
158
  not (Node.failN1 node) && (Node.rMem node >= 0) ==>
159
  not (Node.failN1 (Node.setFmem node (Node.rMem node)))
160

    
161
-- Check if adding an instance that consumes exactly all reserved
162
-- memory does not raise an N+1 error
163
prop_addPri_NoN1Fail :: Property
164
prop_addPri_NoN1Fail =
165
  forAll genOnlineNode $ \node ->
166
  forAll (genInstanceSmallerThanNode node) $ \inst ->
167
  let inst' = inst { Instance.mem = Node.fMem node - Node.rMem node }
168
  in (Node.addPri node inst' /=? Bad Types.FailN1)
169

    
170
-- | Check that an instance add with too high memory or disk will be
171
-- rejected.
172
prop_addPriFM :: Node.Node -> Instance.Instance -> Property
173
prop_addPriFM node inst =
174
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
175
  not (Instance.isOffline inst) ==>
176
  (Node.addPri node inst'' ==? Bad Types.FailMem)
177
  where inst' = setInstanceSmallerThanNode node inst
178
        inst'' = inst' { Instance.mem = Instance.mem inst }
179

    
180
-- | Check that adding a primary instance with too much disk fails
181
-- with type FailDisk.
182
prop_addPriFD :: Node.Node -> Instance.Instance -> Property
183
prop_addPriFD node inst =
184
  forAll (elements Instance.localStorageTemplates) $ \dt ->
185
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
186
  let inst' = setInstanceSmallerThanNode node inst
187
      inst'' = inst' { Instance.dsk = Instance.dsk inst
188
                     , Instance.diskTemplate = dt }
189
  in (Node.addPri node inst'' ==? Bad Types.FailDisk)
190

    
191
-- | Check that adding a primary instance with too many VCPUs fails
192
-- with type FailCPU.
193
prop_addPriFC :: Property
194
prop_addPriFC =
195
  forAll (choose (1, maxCpu)) $ \extra ->
196
  forAll genOnlineNode $ \node ->
197
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
198
  let inst' = setInstanceSmallerThanNode node inst
199
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
200
  in case Node.addPri node inst'' of
201
       Bad Types.FailCPU -> passTest
202
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
203

    
204
-- | Check that an instance add with too high memory or disk will be
205
-- rejected.
206
prop_addSec :: Node.Node -> Instance.Instance -> Int -> Property
207
prop_addSec node inst pdx =
208
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
209
    not (Instance.isOffline inst)) ||
210
   Instance.dsk inst >= Node.fDsk node) &&
211
  not (Node.failN1 node) ==>
212
      isBad (Node.addSec node inst pdx)
213

    
214
-- | Check that an offline instance with reasonable disk size but
215
-- extra mem/cpu can always be added.
216
prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
217
prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
218
  forAll genOnlineNode $ \node ->
219
  forAll (genInstanceSmallerThanNode node) $ \inst ->
220
  let inst' = inst { Instance.runSt = Types.StatusOffline
221
                   , Instance.mem = Node.availMem node + extra_mem
222
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
223
  in case Node.addPri node inst' of
224
       Ok _ -> passTest
225
       v -> failTest $ "Expected OpGood, but got: " ++ show v
226

    
227
-- | Check that an offline instance with reasonable disk size but
228
-- extra mem/cpu can always be added.
229
prop_addOfflineSec :: NonNegative Int -> NonNegative Int
230
                   -> Types.Ndx -> Property
231
prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
232
  forAll genOnlineNode $ \node ->
233
  forAll (genInstanceSmallerThanNode node) $ \inst ->
234
  let inst' = inst { Instance.runSt = Types.StatusOffline
235
                   , Instance.mem = Node.availMem node + extra_mem
236
                   , Instance.vcpus = Node.availCpu node + extra_cpu
237
                   , Instance.diskTemplate = Types.DTDrbd8 }
238
  in case Node.addSec node inst' pdx of
239
       Ok _ -> passTest
240
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
241

    
242
-- | Checks for memory reservation changes.
243
prop_rMem :: Instance.Instance -> Property
244
prop_rMem inst =
245
  not (Instance.isOffline inst) ==>
246
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
247
  -- ab = auto_balance, nb = non-auto_balance
248
  -- we use -1 as the primary node of the instance
249
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
250
                   , Instance.diskTemplate = Types.DTDrbd8 }
251
      inst_ab = setInstanceSmallerThanNode node inst'
252
      inst_nb = inst_ab { Instance.autoBalance = False }
253
      -- now we have the two instances, identical except the
254
      -- autoBalance attribute
255
      orig_rmem = Node.rMem node
256
      inst_idx = Instance.idx inst_ab
257
      node_add_ab = Node.addSec node inst_ab (-1)
258
      node_add_nb = Node.addSec node inst_nb (-1)
259
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
260
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
261
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
262
       (Ok a_ab, Ok a_nb,
263
        Ok d_ab, Ok d_nb) ->
264
         printTestCase "Consistency checks failed" $
265
           Node.rMem a_ab >  orig_rmem &&
266
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
267
           Node.rMem a_nb == orig_rmem &&
268
           Node.rMem d_ab == orig_rmem &&
269
           Node.rMem d_nb == orig_rmem &&
270
           -- this is not related to rMem, but as good a place to
271
           -- test as any
272
           inst_idx `elem` Node.sList a_ab &&
273
           inst_idx `notElem` Node.sList d_ab
274
       x -> failTest $ "Failed to add/remove instances: " ++ show x
275

    
276
-- | Check mdsk setting.
277
prop_setMdsk :: Node.Node -> SmallRatio -> Bool
278
prop_setMdsk node mx =
279
  Node.loDsk node' >= 0 &&
280
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
281
  Node.availDisk node' >= 0 &&
282
  Node.availDisk node' <= Node.fDsk node' &&
283
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
284
  Node.mDsk node' == mx'
285
    where node' = Node.setMdsk node mx'
286
          SmallRatio mx' = mx
287

    
288
-- Check tag maps
289
prop_tagMaps_idempotent :: Property
290
prop_tagMaps_idempotent =
291
  forAll genTags $ \tags ->
292
  Node.delTags (Node.addTags m tags) tags ==? m
293
    where m = Map.empty
294

    
295
prop_tagMaps_reject :: Property
296
prop_tagMaps_reject =
297
  forAll (genTags `suchThat` (not . null)) $ \tags ->
298
  let m = Node.addTags Map.empty tags
299
  in all (\t -> Node.rejectAddTags m [t]) tags
300

    
301
prop_showField :: Node.Node -> Property
302
prop_showField node =
303
  forAll (elements Node.defaultFields) $ \ field ->
304
  fst (Node.showHeader field) /= Types.unknownField &&
305
  Node.showField node field /= Types.unknownField
306

    
307
prop_computeGroups :: [Node.Node] -> Bool
308
prop_computeGroups nodes =
309
  let ng = Node.computeGroups nodes
310
      onlyuuid = map fst ng
311
  in length nodes == sum (map (length . snd) ng) &&
312
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
313
     length (nub onlyuuid) == length onlyuuid &&
314
     (null nodes || not (null ng))
315

    
316
-- Check idempotence of add/remove operations
317
prop_addPri_idempotent :: Property
318
prop_addPri_idempotent =
319
  forAll genOnlineNode $ \node ->
320
  forAll (genInstanceSmallerThanNode node) $ \inst ->
321
  case Node.addPri node inst of
322
    Ok node' -> Node.removePri node' inst ==? node
323
    _ -> failTest "Can't add instance"
324

    
325
prop_addSec_idempotent :: Property
326
prop_addSec_idempotent =
327
  forAll genOnlineNode $ \node ->
328
  forAll (genInstanceSmallerThanNode node) $ \inst ->
329
  let pdx = Node.idx node + 1
330
      inst' = Instance.setPri inst pdx
331
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
332
  in case Node.addSec node inst'' pdx of
333
       Ok node' -> Node.removeSec node' inst'' ==? node
334
       _ -> failTest "Can't add instance"
335

    
336
-- | Check that no graph is created on an empty node list.
337
case_emptyNodeList :: Assertion
338
case_emptyNodeList =
339
  assertEqual "" Nothing $ Node.mkNodeGraph emptynodes emptyinstances
340
    where emptynodes = Container.empty :: Node.List
341
          emptyinstances = Container.empty :: Instance.List
342

    
343
-- | Check that the number of vertices of a nodegraph is equal to the number of
344
-- nodes in the original node list.
345
prop_numVertices :: Property
346
prop_numVertices =
347
  forAll genNodeGraph $ \(graph, nl, _) ->
348
    (fmap numvertices graph ==? Just (Container.size nl))
349
    where numvertices = length . Graph.vertices
350

    
351
-- | Check that the number of edges of a nodegraph is equal to twice the number
352
-- of instances with secondary nodes in the original instance list.
353
prop_numEdges :: Property
354
prop_numEdges =
355
  forAll genNodeGraph $ \(graph, _, il) ->
356
    (fmap numedges graph ==? Just (numwithsec il * 2))
357
    where numedges = length . Graph.edges
358
          numwithsec = length . filter Instance.hasSecondary . Container.elems
359

    
360
-- | Check that a node graph is colorable.
361
prop_nodeGraphIsColorable :: Property
362
prop_nodeGraphIsColorable =
363
  forAll genNodeGraph $ \(graph, _, _) ->
364
    fmap HGraph.isColorable graph ==? Just True
365

    
366
-- | Check that each edge in a nodegraph is an instance.
367
prop_instanceIsEdge :: Property
368
prop_instanceIsEdge =
369
  forAll genNodeGraph $ \(graph, _, il) ->
370
    fmap (\g -> all (`isEdgeOn` g) (iwithsec il)) graph ==? Just True
371
    where i `isEdgeOn` g = iEdges i `intersect` Graph.edges g == iEdges i
372
          iEdges i = [ (Instance.pNode i, Instance.sNode i)
373
                     , (Instance.sNode i, Instance.pNode i)]
374
          iwithsec = filter Instance.hasSecondary . Container.elems
375

    
376
-- | Check that each instance in an edge in the resulting nodegraph.
377
prop_edgeIsInstance :: Property
378
prop_edgeIsInstance =
379
  forAll genNodeGraph $ \(graph, _, il) ->
380
    fmap (all (`isInstanceIn` il).Graph.edges) graph ==? Just True
381
      where e `isInstanceIn` il = any (`hasNodes` e) (Container.elems il)
382
            i `hasNodes` (v1,v2) =
383
              Instance.allNodes i `elem` permutations [v1,v2]
384

    
385
-- | List of tests for the Node module.
386
testSuite "HTools/Node"
387
            [ 'prop_setAlias
388
            , 'prop_setOffline
389
            , 'prop_setMcpu
390
            , 'prop_setFmemGreater
391
            , 'prop_setFmemExact
392
            , 'prop_setXmem
393
            , 'prop_addPriFM
394
            , 'prop_addPriFD
395
            , 'prop_addPriFC
396
            , 'prop_addPri_NoN1Fail
397
            , 'prop_addSec
398
            , 'prop_addOfflinePri
399
            , 'prop_addOfflineSec
400
            , 'prop_rMem
401
            , 'prop_setMdsk
402
            , 'prop_tagMaps_idempotent
403
            , 'prop_tagMaps_reject
404
            , 'prop_showField
405
            , 'prop_computeGroups
406
            , 'prop_addPri_idempotent
407
            , 'prop_addSec_idempotent
408
            , 'case_emptyNodeList
409
            , 'prop_numVertices
410
            , 'prop_numEdges
411
            , 'prop_nodeGraphIsColorable
412
            , 'prop_edgeIsInstance
413
            , 'prop_instanceIsEdge
414
            ]