Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Graph.hs @ 83846468

History | View | Annotate | Download (7 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 if each two consecutive elements on a list
93
-- respect a given condition.
94
anyTwo :: (a -> a -> Bool) -> [a] -> Bool
95
anyTwo _ [] = True
96
anyTwo _ [_] = True
97
anyTwo op (x:y:xs) = (x `op` y) && anyTwo op (y:xs)
98

    
99
-- | Check order of vertices returned by verticesByDegreeAsc.
100
prop_verticesByDegreeAscAsc :: TestableGraph -> Bool
101
prop_verticesByDegreeAscAsc (TestableGraph g) = anyTwo (<=) (degrees asc)
102
    where degrees = map (length . neighbors g)
103
          asc = verticesByDegreeAsc g
104

    
105
-- | Check order of vertices returned by verticesByDegreeDesc.
106
prop_verticesByDegreeDescDesc :: TestableGraph -> Bool
107
prop_verticesByDegreeDescDesc (TestableGraph g) = anyTwo (>=) (degrees desc)
108
    where degrees = map (length . neighbors g)
109
          desc = verticesByDegreeDesc g
110

    
111
-- | Check that our generated graphs are colorable
112
prop_isColorableTestableGraph :: TestableGraph -> Bool
113
prop_isColorableTestableGraph (TestableGraph g) = isColorable g
114

    
115
-- | Check that our generated graphs are colorable
116
prop_isColorableTestableClique :: TestableClique -> Bool
117
prop_isColorableTestableClique (TestableClique g) = isColorable g
118

    
119
-- | Check that the given algorithm colors a clique with the same number of
120
-- colors as the vertices number.
121
prop_colorClique :: (Graph.Graph -> VertColorMap) -> TestableClique -> Property
122
prop_colorClique alg (TestableClique g) = numvertices ==? numcolors
123
    where numcolors = (IntMap.size . colorVertMap) $ alg g
124
          numvertices = length (Graph.vertices g)
125

    
126
-- | Specific check for the LF algorithm.
127
prop_colorLFClique :: TestableClique -> Property
128
prop_colorLFClique = prop_colorClique colorLF
129

    
130
-- | Specific check for the Dsatur algorithm.
131
prop_colorDsaturClique :: TestableClique -> Property
132
prop_colorDsaturClique = prop_colorClique colorDsatur
133

    
134
-- | Specific check for the Dcolor algorithm.
135
prop_colorDcolorClique :: TestableClique -> Property
136
prop_colorDcolorClique = prop_colorClique colorDcolor
137

    
138
-- Check that all nodes are colored.
139
prop_colorAllNodes :: (Graph.Graph -> VertColorMap)
140
                   -> TestableGraph
141
                   -> Property
142
prop_colorAllNodes alg (TestableGraph g) = numvertices ==? numcolored
143
    where numcolored = IntMap.fold ((+) . length) 0 vcMap
144
          vcMap = colorVertMap $ alg g
145
          numvertices = length (Graph.vertices g)
146

    
147
-- | Specific check for the LF algorithm.
148
prop_colorLFAllNodes :: TestableGraph -> Property
149
prop_colorLFAllNodes = prop_colorAllNodes colorLF
150

    
151
-- | Specific check for the Dsatur algorithm.
152
prop_colorDsaturAllNodes :: TestableGraph -> Property
153
prop_colorDsaturAllNodes = prop_colorAllNodes colorDsatur
154

    
155
-- | Specific check for the Dcolor algorithm.
156
prop_colorDcolorAllNodes :: TestableGraph -> Property
157
prop_colorDcolorAllNodes = prop_colorAllNodes colorDcolor
158

    
159
-- | Check that no two vertices sharing the same edge have the same color.
160
prop_colorProper :: (Graph.Graph -> VertColorMap) -> TestableGraph -> Bool
161
prop_colorProper alg (TestableGraph g) = all isEdgeOk $ Graph.edges g
162
    where isEdgeOk :: Graph.Edge -> Bool
163
          isEdgeOk (v1, v2) = color v1 /= color v2
164
          color v = cMap IntMap.! v
165
          cMap = alg g
166

    
167
-- | Specific check for the LF algorithm.
168
prop_colorLFProper :: TestableGraph -> Bool
169
prop_colorLFProper = prop_colorProper colorLF
170

    
171
-- | Specific check for the Dsatur algorithm.
172
prop_colorDsaturProper :: TestableGraph -> Bool
173
prop_colorDsaturProper = prop_colorProper colorDsatur
174

    
175
-- | Specific check for the Dcolor algorithm.
176
prop_colorDcolorProper :: TestableGraph -> Bool
177
prop_colorDcolorProper = prop_colorProper colorDcolor
178

    
179
-- | List of tests for the Graph module.
180
testSuite "HTools/Graph"
181
            [ 'case_emptyVertColorMapNull
182
            , 'case_emptyVertColorMapEmpty
183
            , 'prop_verticesByDegreeAscAsc
184
            , 'prop_verticesByDegreeDescDesc
185
            , 'prop_colorLFClique
186
            , 'prop_colorDsaturClique
187
            , 'prop_colorDcolorClique
188
            , 'prop_colorLFAllNodes
189
            , 'prop_colorDsaturAllNodes
190
            , 'prop_colorDcolorAllNodes
191
            , 'prop_colorLFProper
192
            , 'prop_colorDsaturProper
193
            , 'prop_colorDcolorProper
194
            , 'prop_isColorableTestableGraph
195
            , 'prop_isColorableTestableClique
196
            ]