Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (15.5 kB)

1 e1ee7d5a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 e1ee7d5a Iustin Pop
module Test.Ganeti.HTools.Node
30 e09c1fa0 Iustin Pop
  ( testHTools_Node
31 e1ee7d5a Iustin Pop
  , Node.Node(..)
32 e1ee7d5a Iustin Pop
  , setInstanceSmallerThanNode
33 e1ee7d5a Iustin Pop
  , genNode
34 e1ee7d5a Iustin Pop
  , genOnlineNode
35 736ba160 Guido Trotter
  , genNodeList
36 e1ee7d5a Iustin Pop
  ) where
37 e1ee7d5a Iustin Pop
38 e1ee7d5a Iustin Pop
import Test.QuickCheck
39 dae1f9cb Guido Trotter
import Test.HUnit
40 e1ee7d5a Iustin Pop
41 e1ee7d5a Iustin Pop
import Control.Monad
42 e1ee7d5a Iustin Pop
import qualified Data.Map as Map
43 dae1f9cb Guido Trotter
import qualified Data.Graph as Graph
44 e1ee7d5a Iustin Pop
import Data.List
45 e1ee7d5a Iustin Pop
46 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
47 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
48 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
49 dae1f9cb Guido Trotter
import Test.Ganeti.HTools.Instance ( genInstanceSmallerThanNode
50 dae1f9cb Guido Trotter
                                   , genInstanceList
51 dae1f9cb Guido Trotter
                                   , genInstanceOnNodeList)
52 e1ee7d5a Iustin Pop
53 a8038349 Iustin Pop
import Ganeti.BasicTypes
54 736ba160 Guido Trotter
import qualified Ganeti.HTools.Loader as Loader
55 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
56 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
57 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
58 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
59 dae1f9cb Guido Trotter
import qualified Ganeti.HTools.Graph as HGraph
60 dae1f9cb Guido Trotter
61 dae1f9cb Guido Trotter
{-# ANN module "HLint: ignore Use camelCase" #-}
62 e1ee7d5a Iustin Pop
63 e1ee7d5a Iustin Pop
-- * Arbitrary instances
64 e1ee7d5a Iustin Pop
65 dd77da99 Helga Velroyen
-- | Generates an arbitrary node based on sizing information.
66 e1ee7d5a Iustin Pop
genNode :: Maybe Int -- ^ Minimum node size in terms of units
67 e1ee7d5a Iustin Pop
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
68 e1ee7d5a Iustin Pop
                     -- just by the max... constants)
69 e1ee7d5a Iustin Pop
        -> Gen Node.Node
70 e1ee7d5a Iustin Pop
genNode min_multiplier max_multiplier = do
71 e1ee7d5a Iustin Pop
  let (base_mem, base_dsk, base_cpu) =
72 e1ee7d5a Iustin Pop
        case min_multiplier of
73 e1ee7d5a Iustin Pop
          Just mm -> (mm * Types.unitMem,
74 e1ee7d5a Iustin Pop
                      mm * Types.unitDsk,
75 e1ee7d5a Iustin Pop
                      mm * Types.unitCpu)
76 e1ee7d5a Iustin Pop
          Nothing -> (0, 0, 0)
77 e1ee7d5a Iustin Pop
      (top_mem, top_dsk, top_cpu)  =
78 e1ee7d5a Iustin Pop
        case max_multiplier of
79 e1ee7d5a Iustin Pop
          Just mm -> (mm * Types.unitMem,
80 e1ee7d5a Iustin Pop
                      mm * Types.unitDsk,
81 e1ee7d5a Iustin Pop
                      mm * Types.unitCpu)
82 e1ee7d5a Iustin Pop
          Nothing -> (maxMem, maxDsk, maxCpu)
83 5006418e Iustin Pop
  name  <- genFQDN
84 e1ee7d5a Iustin Pop
  mem_t <- choose (base_mem, top_mem)
85 e1ee7d5a Iustin Pop
  mem_f <- choose (base_mem, mem_t)
86 e1ee7d5a Iustin Pop
  mem_n <- choose (0, mem_t - mem_f)
87 e1ee7d5a Iustin Pop
  dsk_t <- choose (base_dsk, top_dsk)
88 e1ee7d5a Iustin Pop
  dsk_f <- choose (base_dsk, dsk_t)
89 e1ee7d5a Iustin Pop
  cpu_t <- choose (base_cpu, top_cpu)
90 e1ee7d5a Iustin Pop
  offl  <- arbitrary
91 e1ee7d5a Iustin Pop
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
92 e1ee7d5a Iustin Pop
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
93 e1ee7d5a Iustin Pop
      n' = Node.setPolicy nullIPolicy n
94 e1ee7d5a Iustin Pop
  return $ Node.buildPeers n' Container.empty
95 e1ee7d5a Iustin Pop
96 e1ee7d5a Iustin Pop
-- | Helper function to generate a sane node.
97 e1ee7d5a Iustin Pop
genOnlineNode :: Gen Node.Node
98 5b11f8db Iustin Pop
genOnlineNode =
99 e1ee7d5a Iustin Pop
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
100 e1ee7d5a Iustin Pop
                              not (Node.failN1 n) &&
101 e1ee7d5a Iustin Pop
                              Node.availDisk n > 0 &&
102 e1ee7d5a Iustin Pop
                              Node.availMem n > 0 &&
103 e1ee7d5a Iustin Pop
                              Node.availCpu n > 0)
104 e1ee7d5a Iustin Pop
105 e1ee7d5a Iustin Pop
-- and a random node
106 e1ee7d5a Iustin Pop
instance Arbitrary Node.Node where
107 e1ee7d5a Iustin Pop
  arbitrary = genNode Nothing Nothing
108 e1ee7d5a Iustin Pop
109 736ba160 Guido Trotter
-- | Node list generator.
110 736ba160 Guido Trotter
-- Given a node generator, create a random length node list.  Note that "real"
111 736ba160 Guido Trotter
-- clusters always have at least one node, so we don't generate empty node
112 736ba160 Guido Trotter
-- lists here.
113 736ba160 Guido Trotter
genNodeList :: Gen Node.Node -> Gen Node.List
114 736ba160 Guido Trotter
genNodeList ngen = fmap (snd . Loader.assignIndices) names_nodes
115 f9649b3d Klaus Aehlig
    where names_nodes = (fmap . map) (\n -> (Node.name n, n)) nodes
116 f9649b3d Klaus Aehlig
          nodes = listOf1 ngen `suchThat`
117 f9649b3d Klaus Aehlig
                  ((\ns -> ns == nub ns) . map Node.name)
118 736ba160 Guido Trotter
119 dae1f9cb Guido Trotter
-- | Generate a node list, an instance list, and a node graph.
120 dae1f9cb Guido Trotter
-- We choose instances with nodes contained in the node list.
121 dae1f9cb Guido Trotter
genNodeGraph :: Gen (Maybe Graph.Graph, Node.List, Instance.List)
122 dae1f9cb Guido Trotter
genNodeGraph = do
123 dae1f9cb Guido Trotter
  nl <- genNodeList genOnlineNode `suchThat` ((2<=).Container.size)
124 dae1f9cb Guido Trotter
  il <- genInstanceList (genInstanceOnNodeList nl)
125 dae1f9cb Guido Trotter
  return (Node.mkNodeGraph nl il, nl, il)
126 dae1f9cb Guido Trotter
127 e1ee7d5a Iustin Pop
-- * Test cases
128 e1ee7d5a Iustin Pop
129 20bc5360 Iustin Pop
prop_setAlias :: Node.Node -> String -> Bool
130 20bc5360 Iustin Pop
prop_setAlias node name =
131 e1ee7d5a Iustin Pop
  Node.name newnode == Node.name node &&
132 e1ee7d5a Iustin Pop
  Node.alias newnode == name
133 e1ee7d5a Iustin Pop
    where newnode = Node.setAlias node name
134 e1ee7d5a Iustin Pop
135 20bc5360 Iustin Pop
prop_setOffline :: Node.Node -> Bool -> Property
136 20bc5360 Iustin Pop
prop_setOffline node status =
137 e1ee7d5a Iustin Pop
  Node.offline newnode ==? status
138 e1ee7d5a Iustin Pop
    where newnode = Node.setOffline node status
139 e1ee7d5a Iustin Pop
140 20bc5360 Iustin Pop
prop_setXmem :: Node.Node -> Int -> Property
141 20bc5360 Iustin Pop
prop_setXmem node xm =
142 e1ee7d5a Iustin Pop
  Node.xMem newnode ==? xm
143 e1ee7d5a Iustin Pop
    where newnode = Node.setXmem node xm
144 e1ee7d5a Iustin Pop
145 20bc5360 Iustin Pop
prop_setMcpu :: Node.Node -> Double -> Property
146 20bc5360 Iustin Pop
prop_setMcpu node mc =
147 e1ee7d5a Iustin Pop
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
148 e1ee7d5a Iustin Pop
    where newnode = Node.setMcpu node mc
149 e1ee7d5a Iustin Pop
150 77ffd663 Helga Velroyen
prop_setFmemGreater :: Node.Node -> Int -> Property
151 77ffd663 Helga Velroyen
prop_setFmemGreater node new_mem =
152 77ffd663 Helga Velroyen
  not (Node.failN1 node) && (Node.rMem node >= 0) &&
153 77ffd663 Helga Velroyen
  (new_mem > Node.rMem node) ==>
154 77ffd663 Helga Velroyen
  not (Node.failN1 (Node.setFmem node new_mem))
155 77ffd663 Helga Velroyen
156 77ffd663 Helga Velroyen
prop_setFmemExact :: Node.Node -> Property
157 77ffd663 Helga Velroyen
prop_setFmemExact node =
158 77ffd663 Helga Velroyen
  not (Node.failN1 node) && (Node.rMem node >= 0) ==>
159 77ffd663 Helga Velroyen
  not (Node.failN1 (Node.setFmem node (Node.rMem node)))
160 77ffd663 Helga Velroyen
161 77ffd663 Helga Velroyen
-- Check if adding an instance that consumes exactly all reserved
162 77ffd663 Helga Velroyen
-- memory does not raise an N+1 error
163 77ffd663 Helga Velroyen
prop_addPri_NoN1Fail :: Property
164 77ffd663 Helga Velroyen
prop_addPri_NoN1Fail =
165 77ffd663 Helga Velroyen
  forAll genOnlineNode $ \node ->
166 77ffd663 Helga Velroyen
  forAll (genInstanceSmallerThanNode node) $ \inst ->
167 77ffd663 Helga Velroyen
  let inst' = inst { Instance.mem = Node.fMem node - Node.rMem node }
168 dddb2bc9 Helga Velroyen
  in (Node.addPri node inst' /=? Bad Types.FailN1)
169 77ffd663 Helga Velroyen
170 e1ee7d5a Iustin Pop
-- | Check that an instance add with too high memory or disk will be
171 e1ee7d5a Iustin Pop
-- rejected.
172 20bc5360 Iustin Pop
prop_addPriFM :: Node.Node -> Instance.Instance -> Property
173 20bc5360 Iustin Pop
prop_addPriFM node inst =
174 e1ee7d5a Iustin Pop
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
175 e1ee7d5a Iustin Pop
  not (Instance.isOffline inst) ==>
176 dd77da99 Helga Velroyen
  (Node.addPri node inst'' ==? Bad Types.FailMem)
177 e1ee7d5a Iustin Pop
  where inst' = setInstanceSmallerThanNode node inst
178 e1ee7d5a Iustin Pop
        inst'' = inst' { Instance.mem = Instance.mem inst }
179 e1ee7d5a Iustin Pop
180 e1ee7d5a Iustin Pop
-- | Check that adding a primary instance with too much disk fails
181 e1ee7d5a Iustin Pop
-- with type FailDisk.
182 20bc5360 Iustin Pop
prop_addPriFD :: Node.Node -> Instance.Instance -> Property
183 20bc5360 Iustin Pop
prop_addPriFD node inst =
184 e1ee7d5a Iustin Pop
  forAll (elements Instance.localStorageTemplates) $ \dt ->
185 e1ee7d5a Iustin Pop
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
186 e1ee7d5a Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
187 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.dsk = Instance.dsk inst
188 e1ee7d5a Iustin Pop
                     , Instance.diskTemplate = dt }
189 dd77da99 Helga Velroyen
  in (Node.addPri node inst'' ==? Bad Types.FailDisk)
190 e1ee7d5a Iustin Pop
191 e1ee7d5a Iustin Pop
-- | Check that adding a primary instance with too many VCPUs fails
192 e1ee7d5a Iustin Pop
-- with type FailCPU.
193 20bc5360 Iustin Pop
prop_addPriFC :: Property
194 20bc5360 Iustin Pop
prop_addPriFC =
195 e1ee7d5a Iustin Pop
  forAll (choose (1, maxCpu)) $ \extra ->
196 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
197 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
198 e1ee7d5a Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
199 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
200 e1ee7d5a Iustin Pop
  in case Node.addPri node inst'' of
201 a8038349 Iustin Pop
       Bad Types.FailCPU -> passTest
202 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
203 e1ee7d5a Iustin Pop
204 e1ee7d5a Iustin Pop
-- | Check that an instance add with too high memory or disk will be
205 e1ee7d5a Iustin Pop
-- rejected.
206 20bc5360 Iustin Pop
prop_addSec :: Node.Node -> Instance.Instance -> Int -> Property
207 20bc5360 Iustin Pop
prop_addSec node inst pdx =
208 e1ee7d5a Iustin Pop
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
209 e1ee7d5a Iustin Pop
    not (Instance.isOffline inst)) ||
210 e1ee7d5a Iustin Pop
   Instance.dsk inst >= Node.fDsk node) &&
211 e1ee7d5a Iustin Pop
  not (Node.failN1 node) ==>
212 a8038349 Iustin Pop
      isBad (Node.addSec node inst pdx)
213 e1ee7d5a Iustin Pop
214 e1ee7d5a Iustin Pop
-- | Check that an offline instance with reasonable disk size but
215 e1ee7d5a Iustin Pop
-- extra mem/cpu can always be added.
216 20bc5360 Iustin Pop
prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
217 20bc5360 Iustin Pop
prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
218 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
219 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
220 5e9deac0 Iustin Pop
  let inst' = inst { Instance.runSt = Types.StatusOffline
221 e1ee7d5a Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
222 e1ee7d5a Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
223 e1ee7d5a Iustin Pop
  in case Node.addPri node inst' of
224 a8038349 Iustin Pop
       Ok _ -> passTest
225 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpGood, but got: " ++ show v
226 e1ee7d5a Iustin Pop
227 e1ee7d5a Iustin Pop
-- | Check that an offline instance with reasonable disk size but
228 e1ee7d5a Iustin Pop
-- extra mem/cpu can always be added.
229 20bc5360 Iustin Pop
prop_addOfflineSec :: NonNegative Int -> NonNegative Int
230 20bc5360 Iustin Pop
                   -> Types.Ndx -> Property
231 20bc5360 Iustin Pop
prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
232 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
233 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
234 5e9deac0 Iustin Pop
  let inst' = inst { Instance.runSt = Types.StatusOffline
235 e1ee7d5a Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
236 e1ee7d5a Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu
237 e1ee7d5a Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
238 e1ee7d5a Iustin Pop
  in case Node.addSec node inst' pdx of
239 a8038349 Iustin Pop
       Ok _ -> passTest
240 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
241 e1ee7d5a Iustin Pop
242 e1ee7d5a Iustin Pop
-- | Checks for memory reservation changes.
243 20bc5360 Iustin Pop
prop_rMem :: Instance.Instance -> Property
244 20bc5360 Iustin Pop
prop_rMem inst =
245 e1ee7d5a Iustin Pop
  not (Instance.isOffline inst) ==>
246 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
247 e1ee7d5a Iustin Pop
  -- ab = auto_balance, nb = non-auto_balance
248 e1ee7d5a Iustin Pop
  -- we use -1 as the primary node of the instance
249 e1ee7d5a Iustin Pop
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
250 e1ee7d5a Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
251 e1ee7d5a Iustin Pop
      inst_ab = setInstanceSmallerThanNode node inst'
252 e1ee7d5a Iustin Pop
      inst_nb = inst_ab { Instance.autoBalance = False }
253 e1ee7d5a Iustin Pop
      -- now we have the two instances, identical except the
254 e1ee7d5a Iustin Pop
      -- autoBalance attribute
255 e1ee7d5a Iustin Pop
      orig_rmem = Node.rMem node
256 e1ee7d5a Iustin Pop
      inst_idx = Instance.idx inst_ab
257 e1ee7d5a Iustin Pop
      node_add_ab = Node.addSec node inst_ab (-1)
258 e1ee7d5a Iustin Pop
      node_add_nb = Node.addSec node inst_nb (-1)
259 e1ee7d5a Iustin Pop
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
260 e1ee7d5a Iustin Pop
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
261 e1ee7d5a Iustin Pop
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
262 a8038349 Iustin Pop
       (Ok a_ab, Ok a_nb,
263 a8038349 Iustin Pop
        Ok d_ab, Ok d_nb) ->
264 e1ee7d5a Iustin Pop
         printTestCase "Consistency checks failed" $
265 e1ee7d5a Iustin Pop
           Node.rMem a_ab >  orig_rmem &&
266 e1ee7d5a Iustin Pop
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
267 e1ee7d5a Iustin Pop
           Node.rMem a_nb == orig_rmem &&
268 e1ee7d5a Iustin Pop
           Node.rMem d_ab == orig_rmem &&
269 e1ee7d5a Iustin Pop
           Node.rMem d_nb == orig_rmem &&
270 e1ee7d5a Iustin Pop
           -- this is not related to rMem, but as good a place to
271 e1ee7d5a Iustin Pop
           -- test as any
272 e1ee7d5a Iustin Pop
           inst_idx `elem` Node.sList a_ab &&
273 e1ee7d5a Iustin Pop
           inst_idx `notElem` Node.sList d_ab
274 e1ee7d5a Iustin Pop
       x -> failTest $ "Failed to add/remove instances: " ++ show x
275 e1ee7d5a Iustin Pop
276 e1ee7d5a Iustin Pop
-- | Check mdsk setting.
277 20bc5360 Iustin Pop
prop_setMdsk :: Node.Node -> SmallRatio -> Bool
278 20bc5360 Iustin Pop
prop_setMdsk node mx =
279 e1ee7d5a Iustin Pop
  Node.loDsk node' >= 0 &&
280 e1ee7d5a Iustin Pop
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
281 e1ee7d5a Iustin Pop
  Node.availDisk node' >= 0 &&
282 e1ee7d5a Iustin Pop
  Node.availDisk node' <= Node.fDsk node' &&
283 e1ee7d5a Iustin Pop
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
284 e1ee7d5a Iustin Pop
  Node.mDsk node' == mx'
285 e1ee7d5a Iustin Pop
    where node' = Node.setMdsk node mx'
286 e1ee7d5a Iustin Pop
          SmallRatio mx' = mx
287 e1ee7d5a Iustin Pop
288 e1ee7d5a Iustin Pop
-- Check tag maps
289 20bc5360 Iustin Pop
prop_tagMaps_idempotent :: Property
290 20bc5360 Iustin Pop
prop_tagMaps_idempotent =
291 e1ee7d5a Iustin Pop
  forAll genTags $ \tags ->
292 e1ee7d5a Iustin Pop
  Node.delTags (Node.addTags m tags) tags ==? m
293 e1ee7d5a Iustin Pop
    where m = Map.empty
294 e1ee7d5a Iustin Pop
295 20bc5360 Iustin Pop
prop_tagMaps_reject :: Property
296 20bc5360 Iustin Pop
prop_tagMaps_reject =
297 e1ee7d5a Iustin Pop
  forAll (genTags `suchThat` (not . null)) $ \tags ->
298 e1ee7d5a Iustin Pop
  let m = Node.addTags Map.empty tags
299 e1ee7d5a Iustin Pop
  in all (\t -> Node.rejectAddTags m [t]) tags
300 e1ee7d5a Iustin Pop
301 20bc5360 Iustin Pop
prop_showField :: Node.Node -> Property
302 20bc5360 Iustin Pop
prop_showField node =
303 e1ee7d5a Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
304 e1ee7d5a Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
305 e1ee7d5a Iustin Pop
  Node.showField node field /= Types.unknownField
306 e1ee7d5a Iustin Pop
307 20bc5360 Iustin Pop
prop_computeGroups :: [Node.Node] -> Bool
308 20bc5360 Iustin Pop
prop_computeGroups nodes =
309 e1ee7d5a Iustin Pop
  let ng = Node.computeGroups nodes
310 e1ee7d5a Iustin Pop
      onlyuuid = map fst ng
311 e1ee7d5a Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
312 e1ee7d5a Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
313 e1ee7d5a Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
314 e1ee7d5a Iustin Pop
     (null nodes || not (null ng))
315 e1ee7d5a Iustin Pop
316 e1ee7d5a Iustin Pop
-- Check idempotence of add/remove operations
317 20bc5360 Iustin Pop
prop_addPri_idempotent :: Property
318 20bc5360 Iustin Pop
prop_addPri_idempotent =
319 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
320 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
321 e1ee7d5a Iustin Pop
  case Node.addPri node inst of
322 a8038349 Iustin Pop
    Ok node' -> Node.removePri node' inst ==? node
323 e1ee7d5a Iustin Pop
    _ -> failTest "Can't add instance"
324 e1ee7d5a Iustin Pop
325 20bc5360 Iustin Pop
prop_addSec_idempotent :: Property
326 20bc5360 Iustin Pop
prop_addSec_idempotent =
327 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
328 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
329 e1ee7d5a Iustin Pop
  let pdx = Node.idx node + 1
330 e1ee7d5a Iustin Pop
      inst' = Instance.setPri inst pdx
331 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
332 e1ee7d5a Iustin Pop
  in case Node.addSec node inst'' pdx of
333 a8038349 Iustin Pop
       Ok node' -> Node.removeSec node' inst'' ==? node
334 e1ee7d5a Iustin Pop
       _ -> failTest "Can't add instance"
335 e1ee7d5a Iustin Pop
336 dae1f9cb Guido Trotter
-- | Check that no graph is created on an empty node list.
337 dae1f9cb Guido Trotter
case_emptyNodeList :: Assertion
338 dae1f9cb Guido Trotter
case_emptyNodeList =
339 dae1f9cb Guido Trotter
  assertEqual "" Nothing $ Node.mkNodeGraph emptynodes emptyinstances
340 dae1f9cb Guido Trotter
    where emptynodes = Container.empty :: Node.List
341 dae1f9cb Guido Trotter
          emptyinstances = Container.empty :: Instance.List
342 dae1f9cb Guido Trotter
343 dae1f9cb Guido Trotter
-- | Check that the number of vertices of a nodegraph is equal to the number of
344 dae1f9cb Guido Trotter
-- nodes in the original node list.
345 dae1f9cb Guido Trotter
prop_numVertices :: Property
346 dae1f9cb Guido Trotter
prop_numVertices =
347 dae1f9cb Guido Trotter
  forAll genNodeGraph $ \(graph, nl, _) ->
348 dae1f9cb Guido Trotter
    (fmap numvertices graph ==? Just (Container.size nl))
349 dae1f9cb Guido Trotter
    where numvertices = length . Graph.vertices
350 dae1f9cb Guido Trotter
351 dae1f9cb Guido Trotter
-- | Check that the number of edges of a nodegraph is equal to twice the number
352 dae1f9cb Guido Trotter
-- of instances with secondary nodes in the original instance list.
353 dae1f9cb Guido Trotter
prop_numEdges :: Property
354 dae1f9cb Guido Trotter
prop_numEdges =
355 dae1f9cb Guido Trotter
  forAll genNodeGraph $ \(graph, _, il) ->
356 dae1f9cb Guido Trotter
    (fmap numedges graph ==? Just (numwithsec il * 2))
357 dae1f9cb Guido Trotter
    where numedges = length . Graph.edges
358 dae1f9cb Guido Trotter
          numwithsec = length . filter Instance.hasSecondary . Container.elems
359 dae1f9cb Guido Trotter
360 dae1f9cb Guido Trotter
-- | Check that a node graph is colorable.
361 dae1f9cb Guido Trotter
prop_nodeGraphIsColorable :: Property
362 dae1f9cb Guido Trotter
prop_nodeGraphIsColorable =
363 dae1f9cb Guido Trotter
  forAll genNodeGraph $ \(graph, _, _) ->
364 dae1f9cb Guido Trotter
    fmap HGraph.isColorable graph ==? Just True
365 dae1f9cb Guido Trotter
366 dae1f9cb Guido Trotter
-- | Check that each edge in a nodegraph is an instance.
367 dae1f9cb Guido Trotter
prop_instanceIsEdge :: Property
368 dae1f9cb Guido Trotter
prop_instanceIsEdge =
369 dae1f9cb Guido Trotter
  forAll genNodeGraph $ \(graph, _, il) ->
370 dae1f9cb Guido Trotter
    fmap (\g -> all (`isEdgeOn` g) (iwithsec il)) graph ==? Just True
371 dae1f9cb Guido Trotter
    where i `isEdgeOn` g = iEdges i `intersect` Graph.edges g == iEdges i
372 dae1f9cb Guido Trotter
          iEdges i = [ (Instance.pNode i, Instance.sNode i)
373 dae1f9cb Guido Trotter
                     , (Instance.sNode i, Instance.pNode i)]
374 dae1f9cb Guido Trotter
          iwithsec = filter Instance.hasSecondary . Container.elems
375 dae1f9cb Guido Trotter
376 dae1f9cb Guido Trotter
-- | Check that each instance in an edge in the resulting nodegraph.
377 dae1f9cb Guido Trotter
prop_edgeIsInstance :: Property
378 dae1f9cb Guido Trotter
prop_edgeIsInstance =
379 dae1f9cb Guido Trotter
  forAll genNodeGraph $ \(graph, _, il) ->
380 dae1f9cb Guido Trotter
    fmap (all (`isInstanceIn` il).Graph.edges) graph ==? Just True
381 dae1f9cb Guido Trotter
      where e `isInstanceIn` il = any (`hasNodes` e) (Container.elems il)
382 dae1f9cb Guido Trotter
            i `hasNodes` (v1,v2) =
383 dae1f9cb Guido Trotter
              Instance.allNodes i `elem` permutations [v1,v2]
384 dae1f9cb Guido Trotter
385 dae1f9cb Guido Trotter
-- | List of tests for the Node module.
386 e09c1fa0 Iustin Pop
testSuite "HTools/Node"
387 20bc5360 Iustin Pop
            [ 'prop_setAlias
388 20bc5360 Iustin Pop
            , 'prop_setOffline
389 20bc5360 Iustin Pop
            , 'prop_setMcpu
390 77ffd663 Helga Velroyen
            , 'prop_setFmemGreater
391 77ffd663 Helga Velroyen
            , 'prop_setFmemExact
392 20bc5360 Iustin Pop
            , 'prop_setXmem
393 20bc5360 Iustin Pop
            , 'prop_addPriFM
394 20bc5360 Iustin Pop
            , 'prop_addPriFD
395 20bc5360 Iustin Pop
            , 'prop_addPriFC
396 77ffd663 Helga Velroyen
            , 'prop_addPri_NoN1Fail
397 20bc5360 Iustin Pop
            , 'prop_addSec
398 20bc5360 Iustin Pop
            , 'prop_addOfflinePri
399 20bc5360 Iustin Pop
            , 'prop_addOfflineSec
400 20bc5360 Iustin Pop
            , 'prop_rMem
401 20bc5360 Iustin Pop
            , 'prop_setMdsk
402 20bc5360 Iustin Pop
            , 'prop_tagMaps_idempotent
403 20bc5360 Iustin Pop
            , 'prop_tagMaps_reject
404 20bc5360 Iustin Pop
            , 'prop_showField
405 20bc5360 Iustin Pop
            , 'prop_computeGroups
406 20bc5360 Iustin Pop
            , 'prop_addPri_idempotent
407 20bc5360 Iustin Pop
            , 'prop_addSec_idempotent
408 dae1f9cb Guido Trotter
            , 'case_emptyNodeList
409 dae1f9cb Guido Trotter
            , 'prop_numVertices
410 dae1f9cb Guido Trotter
            , 'prop_numEdges
411 dae1f9cb Guido Trotter
            , 'prop_nodeGraphIsColorable
412 dae1f9cb Guido Trotter
            , 'prop_edgeIsInstance
413 dae1f9cb Guido Trotter
            , 'prop_instanceIsEdge
414 e1ee7d5a Iustin Pop
            ]