Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Graph.hs @ 8e6623c8

History | View | Annotate | Download (4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for Ganeti.Htools.Graph
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.Graph (testHTools_Graph) where
30

    
31
import Test.QuickCheck
32
import Test.HUnit
33

    
34
import Test.Ganeti.TestHelper
35
import Test.Ganeti.TestCommon
36

    
37
import Ganeti.HTools.Graph
38

    
39
import qualified Data.Graph as Graph
40
import qualified Data.IntMap as IntMap
41

    
42
{-# ANN module "HLint: ignore Use camelCase" #-}
43

    
44
data TestableGraph = TestableGraph Graph.Graph deriving (Show)
45
data TestableClique = TestableClique Graph.Graph deriving (Show)
46

    
47
-- | Generate node bounds and edges for an undirected graph.
48
-- A graph is undirected if for every (a, b) edge there is a
49
-- corresponding (b, a) one.
50
undirEdges :: Gen (Graph.Bounds, [Graph.Edge])
51
undirEdges = sized undirEdges'
52
  where
53
    undirEdges' 0 = return ((0, 0), [])
54
    undirEdges' n = do
55
      maxv <- choose (1, n)
56
      edges <- listOf1 $ do
57
        i <- choose (0, maxv)
58
        j <- choose (0, maxv) `suchThat` (/= i)
59
        return [(i, j), (j, i)]
60
      return ((0, maxv), concat edges)
61

    
62
-- | Generate node bounds and edges for a clique.
63
-- In a clique all nodes are directly connected to each other.
64
cliqueEdges :: Gen (Graph.Bounds, [Graph.Edge])
65
cliqueEdges = sized cliqueEdges'
66
  where
67
    cliqueEdges' 0 = return ((0, 0), [])
68
    cliqueEdges' n = do
69
      maxv <- choose (0, n)
70
      let edges = [(x, y) | x <- [0..maxv], y <- [0..maxv], x /= y]
71
      return ((0, maxv), edges)
72

    
73
instance Arbitrary TestableGraph where
74
  arbitrary = do
75
    (mybounds, myedges) <- undirEdges
76
    return . TestableGraph $ Graph.buildG mybounds myedges
77

    
78
instance Arbitrary TestableClique where
79
  arbitrary = do
80
    (mybounds, myedges) <- cliqueEdges
81
    return . TestableClique $ Graph.buildG mybounds myedges
82

    
83
-- | Check that the empty vertex color map is empty.
84
case_emptyVertColorMapNull :: Assertion
85
case_emptyVertColorMapNull = assertBool "" $ IntMap.null emptyVertColorMap
86

    
87
-- | Check that the empty vertex color map is zero in size.
88
case_emptyVertColorMapEmpty :: Assertion
89
case_emptyVertColorMapEmpty =
90
  assertEqual "" 0 $ IntMap.size emptyVertColorMap
91

    
92
-- | Check that the given algorithm colors a clique with the same number of
93
-- colors as the vertices number.
94
prop_colorClique :: (Graph.Graph -> ColorVertMap) -> TestableClique -> Property
95
prop_colorClique alg (TestableClique g) = numvertices ==? numcolors
96
    where numcolors = IntMap.size (alg g)
97
          numvertices = length (Graph.vertices g)
98

    
99
-- | Specific check for the LF algorithm.
100
prop_colorLFClique :: TestableClique -> Property
101
prop_colorLFClique = prop_colorClique colorLF
102

    
103
-- Check that all nodes are colored.
104
prop_colorAllNodes :: (Graph.Graph -> ColorVertMap)
105
                   -> TestableGraph
106
                   -> Property
107
prop_colorAllNodes alg (TestableGraph g) = numvertices ==? numcolored
108
    where numcolored = IntMap.fold (\v l -> length v + l) 0 $ alg g
109
          numvertices = length (Graph.vertices g)
110

    
111
-- | Specific check for the LF algorithm.
112
prop_colorLFAllNodes :: TestableGraph -> Property
113
prop_colorLFAllNodes = prop_colorAllNodes colorLF
114

    
115
-- | List of tests for the Graph module.
116
testSuite "HTools/Graph"
117
            [ 'case_emptyVertColorMapNull
118
            , 'case_emptyVertColorMapEmpty
119
            , 'prop_colorLFClique
120
            , 'prop_colorLFAllNodes
121
            ]