Revision dae1f9cb htest/Test/Ganeti/HTools/Node.hs

b/htest/Test/Ganeti/HTools/Node.hs
36 36
  ) where
37 37

  
38 38
import Test.QuickCheck
39
import Test.HUnit
39 40

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

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

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

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

  
56 63
-- * Arbitrary instances
57 64

  
......
107 114
genNodeList ngen = fmap (snd . Loader.assignIndices) names_nodes
108 115
    where names_nodes = (fmap . map) (\n -> (Node.name n, n)) $ listOf1 ngen
109 116

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

  
110 125
-- * Test cases
111 126

  
112 127
prop_setAlias :: Node.Node -> String -> Bool
......
316 331
       Ok node' -> Node.removeSec node' inst'' ==? node
317 332
       _ -> failTest "Can't add instance"
318 333

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

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

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

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

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

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

  
383
-- | List of tests for the Node module.
319 384
testSuite "HTools/Node"
320 385
            [ 'prop_setAlias
321 386
            , 'prop_setOffline
......
338 403
            , 'prop_computeGroups
339 404
            , 'prop_addPri_idempotent
340 405
            , 'prop_addSec_idempotent
406
            , 'case_emptyNodeList
407
            , 'prop_numVertices
408
            , 'prop_numEdges
409
            , 'prop_nodeGraphIsColorable
410
            , 'prop_edgeIsInstance
411
            , 'prop_instanceIsEdge
341 412
            ]

Also available in: Unified diff