Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Graph.hs @ dae1f9cb

History | View | Annotate | Download (5.7 kB)

1 8e6623c8 Guido Trotter
{-# LANGUAGE TemplateHaskell #-}
2 8e6623c8 Guido Trotter
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 8e6623c8 Guido Trotter
4 8e6623c8 Guido Trotter
{-| Unittests for Ganeti.Htools.Graph
5 8e6623c8 Guido Trotter
6 8e6623c8 Guido Trotter
-}
7 8e6623c8 Guido Trotter
8 8e6623c8 Guido Trotter
{-
9 8e6623c8 Guido Trotter
10 8e6623c8 Guido Trotter
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 8e6623c8 Guido Trotter
12 8e6623c8 Guido Trotter
This program is free software; you can redistribute it and/or modify
13 8e6623c8 Guido Trotter
it under the terms of the GNU General Public License as published by
14 8e6623c8 Guido Trotter
the Free Software Foundation; either version 2 of the License, or
15 8e6623c8 Guido Trotter
(at your option) any later version.
16 8e6623c8 Guido Trotter
17 8e6623c8 Guido Trotter
This program is distributed in the hope that it will be useful, but
18 8e6623c8 Guido Trotter
WITHOUT ANY WARRANTY; without even the implied warranty of
19 8e6623c8 Guido Trotter
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 8e6623c8 Guido Trotter
General Public License for more details.
21 8e6623c8 Guido Trotter
22 8e6623c8 Guido Trotter
You should have received a copy of the GNU General Public License
23 8e6623c8 Guido Trotter
along with this program; if not, write to the Free Software
24 8e6623c8 Guido Trotter
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 8e6623c8 Guido Trotter
02110-1301, USA.
26 8e6623c8 Guido Trotter
27 8e6623c8 Guido Trotter
-}
28 8e6623c8 Guido Trotter
29 8e6623c8 Guido Trotter
module Test.Ganeti.HTools.Graph (testHTools_Graph) where
30 8e6623c8 Guido Trotter
31 8e6623c8 Guido Trotter
import Test.QuickCheck
32 8e6623c8 Guido Trotter
import Test.HUnit
33 8e6623c8 Guido Trotter
34 8e6623c8 Guido Trotter
import Test.Ganeti.TestHelper
35 8e6623c8 Guido Trotter
import Test.Ganeti.TestCommon
36 8e6623c8 Guido Trotter
37 8e6623c8 Guido Trotter
import Ganeti.HTools.Graph
38 8e6623c8 Guido Trotter
39 8e6623c8 Guido Trotter
import qualified Data.Graph as Graph
40 8e6623c8 Guido Trotter
import qualified Data.IntMap as IntMap
41 8e6623c8 Guido Trotter
42 8e6623c8 Guido Trotter
{-# ANN module "HLint: ignore Use camelCase" #-}
43 8e6623c8 Guido Trotter
44 8e6623c8 Guido Trotter
data TestableGraph = TestableGraph Graph.Graph deriving (Show)
45 8e6623c8 Guido Trotter
data TestableClique = TestableClique Graph.Graph deriving (Show)
46 8e6623c8 Guido Trotter
47 8e6623c8 Guido Trotter
-- | Generate node bounds and edges for an undirected graph.
48 8e6623c8 Guido Trotter
-- A graph is undirected if for every (a, b) edge there is a
49 8e6623c8 Guido Trotter
-- corresponding (b, a) one.
50 8e6623c8 Guido Trotter
undirEdges :: Gen (Graph.Bounds, [Graph.Edge])
51 8e6623c8 Guido Trotter
undirEdges = sized undirEdges'
52 8e6623c8 Guido Trotter
  where
53 8e6623c8 Guido Trotter
    undirEdges' 0 = return ((0, 0), [])
54 8e6623c8 Guido Trotter
    undirEdges' n = do
55 8e6623c8 Guido Trotter
      maxv <- choose (1, n)
56 8e6623c8 Guido Trotter
      edges <- listOf1 $ do
57 8e6623c8 Guido Trotter
        i <- choose (0, maxv)
58 8e6623c8 Guido Trotter
        j <- choose (0, maxv) `suchThat` (/= i)
59 8e6623c8 Guido Trotter
        return [(i, j), (j, i)]
60 8e6623c8 Guido Trotter
      return ((0, maxv), concat edges)
61 8e6623c8 Guido Trotter
62 8e6623c8 Guido Trotter
-- | Generate node bounds and edges for a clique.
63 8e6623c8 Guido Trotter
-- In a clique all nodes are directly connected to each other.
64 8e6623c8 Guido Trotter
cliqueEdges :: Gen (Graph.Bounds, [Graph.Edge])
65 8e6623c8 Guido Trotter
cliqueEdges = sized cliqueEdges'
66 8e6623c8 Guido Trotter
  where
67 8e6623c8 Guido Trotter
    cliqueEdges' 0 = return ((0, 0), [])
68 8e6623c8 Guido Trotter
    cliqueEdges' n = do
69 8e6623c8 Guido Trotter
      maxv <- choose (0, n)
70 8e6623c8 Guido Trotter
      let edges = [(x, y) | x <- [0..maxv], y <- [0..maxv], x /= y]
71 8e6623c8 Guido Trotter
      return ((0, maxv), edges)
72 8e6623c8 Guido Trotter
73 8e6623c8 Guido Trotter
instance Arbitrary TestableGraph where
74 8e6623c8 Guido Trotter
  arbitrary = do
75 8e6623c8 Guido Trotter
    (mybounds, myedges) <- undirEdges
76 8e6623c8 Guido Trotter
    return . TestableGraph $ Graph.buildG mybounds myedges
77 8e6623c8 Guido Trotter
78 8e6623c8 Guido Trotter
instance Arbitrary TestableClique where
79 8e6623c8 Guido Trotter
  arbitrary = do
80 8e6623c8 Guido Trotter
    (mybounds, myedges) <- cliqueEdges
81 8e6623c8 Guido Trotter
    return . TestableClique $ Graph.buildG mybounds myedges
82 8e6623c8 Guido Trotter
83 8e6623c8 Guido Trotter
-- | Check that the empty vertex color map is empty.
84 8e6623c8 Guido Trotter
case_emptyVertColorMapNull :: Assertion
85 8e6623c8 Guido Trotter
case_emptyVertColorMapNull = assertBool "" $ IntMap.null emptyVertColorMap
86 8e6623c8 Guido Trotter
87 8e6623c8 Guido Trotter
-- | Check that the empty vertex color map is zero in size.
88 8e6623c8 Guido Trotter
case_emptyVertColorMapEmpty :: Assertion
89 8e6623c8 Guido Trotter
case_emptyVertColorMapEmpty =
90 8e6623c8 Guido Trotter
  assertEqual "" 0 $ IntMap.size emptyVertColorMap
91 8e6623c8 Guido Trotter
92 34a21cc4 Guido Trotter
-- | Check if each two consecutive elements on a list
93 34a21cc4 Guido Trotter
-- respect a given condition.
94 34a21cc4 Guido Trotter
anyTwo :: (a -> a -> Bool) -> [a] -> Bool
95 34a21cc4 Guido Trotter
anyTwo _ [] = True
96 34a21cc4 Guido Trotter
anyTwo _ [_] = True
97 34a21cc4 Guido Trotter
anyTwo op (x:y:xs) = (x `op` y) && anyTwo op (y:xs)
98 34a21cc4 Guido Trotter
99 34a21cc4 Guido Trotter
-- | Check order of vertices returned by verticesByDegreeAsc.
100 34a21cc4 Guido Trotter
prop_verticesByDegreeAscAsc :: TestableGraph -> Property
101 34a21cc4 Guido Trotter
prop_verticesByDegreeAscAsc (TestableGraph g) =
102 34a21cc4 Guido Trotter
    anyTwo (<=) (degrees asc) ==? True
103 34a21cc4 Guido Trotter
    where degrees = map (length . neighbors g)
104 34a21cc4 Guido Trotter
          asc = verticesByDegreeAsc g
105 34a21cc4 Guido Trotter
106 34a21cc4 Guido Trotter
-- | Check order of vertices returned by verticesByDegreeDesc.
107 34a21cc4 Guido Trotter
prop_verticesByDegreeDescDesc :: TestableGraph -> Property
108 34a21cc4 Guido Trotter
prop_verticesByDegreeDescDesc (TestableGraph g) =
109 34a21cc4 Guido Trotter
    anyTwo (>=) (degrees desc) ==? True
110 34a21cc4 Guido Trotter
    where degrees = map (length . neighbors g)
111 34a21cc4 Guido Trotter
          desc = verticesByDegreeDesc g
112 34a21cc4 Guido Trotter
113 faef859e Guido Trotter
-- | Check that our generated graphs are colorable
114 faef859e Guido Trotter
prop_isColorableTestableGraph :: TestableGraph -> Property
115 faef859e Guido Trotter
prop_isColorableTestableGraph (TestableGraph g) = isColorable g ==? True
116 faef859e Guido Trotter
117 faef859e Guido Trotter
-- | Check that our generated graphs are colorable
118 faef859e Guido Trotter
prop_isColorableTestableClique :: TestableClique -> Property
119 faef859e Guido Trotter
prop_isColorableTestableClique (TestableClique g) = isColorable g ==? True
120 faef859e Guido Trotter
121 8e6623c8 Guido Trotter
-- | Check that the given algorithm colors a clique with the same number of
122 8e6623c8 Guido Trotter
-- colors as the vertices number.
123 8e6623c8 Guido Trotter
prop_colorClique :: (Graph.Graph -> ColorVertMap) -> TestableClique -> Property
124 8e6623c8 Guido Trotter
prop_colorClique alg (TestableClique g) = numvertices ==? numcolors
125 8e6623c8 Guido Trotter
    where numcolors = IntMap.size (alg g)
126 8e6623c8 Guido Trotter
          numvertices = length (Graph.vertices g)
127 8e6623c8 Guido Trotter
128 8e6623c8 Guido Trotter
-- | Specific check for the LF algorithm.
129 8e6623c8 Guido Trotter
prop_colorLFClique :: TestableClique -> Property
130 8e6623c8 Guido Trotter
prop_colorLFClique = prop_colorClique colorLF
131 8e6623c8 Guido Trotter
132 742bd043 Guido Trotter
-- | Specific check for the Dsatur algorithm.
133 742bd043 Guido Trotter
prop_colorDsaturClique :: TestableClique -> Property
134 742bd043 Guido Trotter
prop_colorDsaturClique = prop_colorClique colorDsatur
135 742bd043 Guido Trotter
136 8e6623c8 Guido Trotter
-- Check that all nodes are colored.
137 8e6623c8 Guido Trotter
prop_colorAllNodes :: (Graph.Graph -> ColorVertMap)
138 8e6623c8 Guido Trotter
                   -> TestableGraph
139 8e6623c8 Guido Trotter
                   -> Property
140 8e6623c8 Guido Trotter
prop_colorAllNodes alg (TestableGraph g) = numvertices ==? numcolored
141 8e6623c8 Guido Trotter
    where numcolored = IntMap.fold (\v l -> length v + l) 0 $ alg g
142 8e6623c8 Guido Trotter
          numvertices = length (Graph.vertices g)
143 8e6623c8 Guido Trotter
144 8e6623c8 Guido Trotter
-- | Specific check for the LF algorithm.
145 8e6623c8 Guido Trotter
prop_colorLFAllNodes :: TestableGraph -> Property
146 8e6623c8 Guido Trotter
prop_colorLFAllNodes = prop_colorAllNodes colorLF
147 8e6623c8 Guido Trotter
148 742bd043 Guido Trotter
-- | Specific check for the Dsatur algorithm.
149 742bd043 Guido Trotter
prop_colorDsaturAllNodes :: TestableGraph -> Property
150 742bd043 Guido Trotter
prop_colorDsaturAllNodes = prop_colorAllNodes colorDsatur
151 742bd043 Guido Trotter
152 8e6623c8 Guido Trotter
-- | List of tests for the Graph module.
153 8e6623c8 Guido Trotter
testSuite "HTools/Graph"
154 8e6623c8 Guido Trotter
            [ 'case_emptyVertColorMapNull
155 8e6623c8 Guido Trotter
            , 'case_emptyVertColorMapEmpty
156 34a21cc4 Guido Trotter
            , 'prop_verticesByDegreeAscAsc
157 34a21cc4 Guido Trotter
            , 'prop_verticesByDegreeDescDesc
158 8e6623c8 Guido Trotter
            , 'prop_colorLFClique
159 742bd043 Guido Trotter
            , 'prop_colorDsaturClique
160 8e6623c8 Guido Trotter
            , 'prop_colorLFAllNodes
161 742bd043 Guido Trotter
            , 'prop_colorDsaturAllNodes
162 faef859e Guido Trotter
            , 'prop_isColorableTestableGraph
163 faef859e Guido Trotter
            , 'prop_isColorableTestableClique
164 8e6623c8 Guido Trotter
            ]