Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Node.hs @ 7022db83

History | View | Annotate | Download (11.3 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 e1ee7d5a Iustin Pop
  ) where
36 e1ee7d5a Iustin Pop
37 e1ee7d5a Iustin Pop
import Test.QuickCheck
38 e1ee7d5a Iustin Pop
39 e1ee7d5a Iustin Pop
import Control.Monad
40 e1ee7d5a Iustin Pop
import qualified Data.Map as Map
41 e1ee7d5a Iustin Pop
import Data.List
42 e1ee7d5a Iustin Pop
43 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
44 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
45 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
46 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Instance (genInstanceSmallerThanNode)
47 e1ee7d5a Iustin Pop
48 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
49 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
50 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
51 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
52 e1ee7d5a Iustin Pop
53 e1ee7d5a Iustin Pop
-- * Arbitrary instances
54 e1ee7d5a Iustin Pop
55 e1ee7d5a Iustin Pop
-- | Generas an arbitrary node based on sizing information.
56 e1ee7d5a Iustin Pop
genNode :: Maybe Int -- ^ Minimum node size in terms of units
57 e1ee7d5a Iustin Pop
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
58 e1ee7d5a Iustin Pop
                     -- just by the max... constants)
59 e1ee7d5a Iustin Pop
        -> Gen Node.Node
60 e1ee7d5a Iustin Pop
genNode min_multiplier max_multiplier = do
61 e1ee7d5a Iustin Pop
  let (base_mem, base_dsk, base_cpu) =
62 e1ee7d5a Iustin Pop
        case min_multiplier of
63 e1ee7d5a Iustin Pop
          Just mm -> (mm * Types.unitMem,
64 e1ee7d5a Iustin Pop
                      mm * Types.unitDsk,
65 e1ee7d5a Iustin Pop
                      mm * Types.unitCpu)
66 e1ee7d5a Iustin Pop
          Nothing -> (0, 0, 0)
67 e1ee7d5a Iustin Pop
      (top_mem, top_dsk, top_cpu)  =
68 e1ee7d5a Iustin Pop
        case max_multiplier of
69 e1ee7d5a Iustin Pop
          Just mm -> (mm * Types.unitMem,
70 e1ee7d5a Iustin Pop
                      mm * Types.unitDsk,
71 e1ee7d5a Iustin Pop
                      mm * Types.unitCpu)
72 e1ee7d5a Iustin Pop
          Nothing -> (maxMem, maxDsk, maxCpu)
73 e1ee7d5a Iustin Pop
  name  <- getFQDN
74 e1ee7d5a Iustin Pop
  mem_t <- choose (base_mem, top_mem)
75 e1ee7d5a Iustin Pop
  mem_f <- choose (base_mem, mem_t)
76 e1ee7d5a Iustin Pop
  mem_n <- choose (0, mem_t - mem_f)
77 e1ee7d5a Iustin Pop
  dsk_t <- choose (base_dsk, top_dsk)
78 e1ee7d5a Iustin Pop
  dsk_f <- choose (base_dsk, dsk_t)
79 e1ee7d5a Iustin Pop
  cpu_t <- choose (base_cpu, top_cpu)
80 e1ee7d5a Iustin Pop
  offl  <- arbitrary
81 e1ee7d5a Iustin Pop
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
82 e1ee7d5a Iustin Pop
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
83 e1ee7d5a Iustin Pop
      n' = Node.setPolicy nullIPolicy n
84 e1ee7d5a Iustin Pop
  return $ Node.buildPeers n' Container.empty
85 e1ee7d5a Iustin Pop
86 e1ee7d5a Iustin Pop
-- | Helper function to generate a sane node.
87 e1ee7d5a Iustin Pop
genOnlineNode :: Gen Node.Node
88 e1ee7d5a Iustin Pop
genOnlineNode = do
89 e1ee7d5a Iustin Pop
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
90 e1ee7d5a Iustin Pop
                              not (Node.failN1 n) &&
91 e1ee7d5a Iustin Pop
                              Node.availDisk n > 0 &&
92 e1ee7d5a Iustin Pop
                              Node.availMem n > 0 &&
93 e1ee7d5a Iustin Pop
                              Node.availCpu n > 0)
94 e1ee7d5a Iustin Pop
95 e1ee7d5a Iustin Pop
-- and a random node
96 e1ee7d5a Iustin Pop
instance Arbitrary Node.Node where
97 e1ee7d5a Iustin Pop
  arbitrary = genNode Nothing Nothing
98 e1ee7d5a Iustin Pop
99 e1ee7d5a Iustin Pop
-- * Test cases
100 e1ee7d5a Iustin Pop
101 20bc5360 Iustin Pop
prop_setAlias :: Node.Node -> String -> Bool
102 20bc5360 Iustin Pop
prop_setAlias node name =
103 e1ee7d5a Iustin Pop
  Node.name newnode == Node.name node &&
104 e1ee7d5a Iustin Pop
  Node.alias newnode == name
105 e1ee7d5a Iustin Pop
    where newnode = Node.setAlias node name
106 e1ee7d5a Iustin Pop
107 20bc5360 Iustin Pop
prop_setOffline :: Node.Node -> Bool -> Property
108 20bc5360 Iustin Pop
prop_setOffline node status =
109 e1ee7d5a Iustin Pop
  Node.offline newnode ==? status
110 e1ee7d5a Iustin Pop
    where newnode = Node.setOffline node status
111 e1ee7d5a Iustin Pop
112 20bc5360 Iustin Pop
prop_setXmem :: Node.Node -> Int -> Property
113 20bc5360 Iustin Pop
prop_setXmem node xm =
114 e1ee7d5a Iustin Pop
  Node.xMem newnode ==? xm
115 e1ee7d5a Iustin Pop
    where newnode = Node.setXmem node xm
116 e1ee7d5a Iustin Pop
117 20bc5360 Iustin Pop
prop_setMcpu :: Node.Node -> Double -> Property
118 20bc5360 Iustin Pop
prop_setMcpu node mc =
119 e1ee7d5a Iustin Pop
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
120 e1ee7d5a Iustin Pop
    where newnode = Node.setMcpu node mc
121 e1ee7d5a Iustin Pop
122 e1ee7d5a Iustin Pop
-- | Check that an instance add with too high memory or disk will be
123 e1ee7d5a Iustin Pop
-- rejected.
124 20bc5360 Iustin Pop
prop_addPriFM :: Node.Node -> Instance.Instance -> Property
125 20bc5360 Iustin Pop
prop_addPriFM node inst =
126 e1ee7d5a Iustin Pop
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
127 e1ee7d5a Iustin Pop
  not (Instance.isOffline inst) ==>
128 e1ee7d5a Iustin Pop
  case Node.addPri node inst'' of
129 e1ee7d5a Iustin Pop
    Types.OpFail Types.FailMem -> True
130 e1ee7d5a Iustin Pop
    _ -> False
131 e1ee7d5a Iustin Pop
  where inst' = setInstanceSmallerThanNode node inst
132 e1ee7d5a Iustin Pop
        inst'' = inst' { Instance.mem = Instance.mem inst }
133 e1ee7d5a Iustin Pop
134 e1ee7d5a Iustin Pop
-- | Check that adding a primary instance with too much disk fails
135 e1ee7d5a Iustin Pop
-- with type FailDisk.
136 20bc5360 Iustin Pop
prop_addPriFD :: Node.Node -> Instance.Instance -> Property
137 20bc5360 Iustin Pop
prop_addPriFD node inst =
138 e1ee7d5a Iustin Pop
  forAll (elements Instance.localStorageTemplates) $ \dt ->
139 e1ee7d5a Iustin Pop
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
140 e1ee7d5a Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
141 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.dsk = Instance.dsk inst
142 e1ee7d5a Iustin Pop
                     , Instance.diskTemplate = dt }
143 e1ee7d5a Iustin Pop
  in case Node.addPri node inst'' of
144 e1ee7d5a Iustin Pop
       Types.OpFail Types.FailDisk -> True
145 e1ee7d5a Iustin Pop
       _ -> False
146 e1ee7d5a Iustin Pop
147 e1ee7d5a Iustin Pop
-- | Check that adding a primary instance with too many VCPUs fails
148 e1ee7d5a Iustin Pop
-- with type FailCPU.
149 20bc5360 Iustin Pop
prop_addPriFC :: Property
150 20bc5360 Iustin Pop
prop_addPriFC =
151 e1ee7d5a Iustin Pop
  forAll (choose (1, maxCpu)) $ \extra ->
152 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
153 e1ee7d5a Iustin Pop
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
154 e1ee7d5a Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
155 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
156 e1ee7d5a Iustin Pop
  in case Node.addPri node inst'' of
157 e1ee7d5a Iustin Pop
       Types.OpFail Types.FailCPU -> property True
158 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
159 e1ee7d5a Iustin Pop
160 e1ee7d5a Iustin Pop
-- | Check that an instance add with too high memory or disk will be
161 e1ee7d5a Iustin Pop
-- rejected.
162 20bc5360 Iustin Pop
prop_addSec :: Node.Node -> Instance.Instance -> Int -> Property
163 20bc5360 Iustin Pop
prop_addSec node inst pdx =
164 e1ee7d5a Iustin Pop
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
165 e1ee7d5a Iustin Pop
    not (Instance.isOffline inst)) ||
166 e1ee7d5a Iustin Pop
   Instance.dsk inst >= Node.fDsk node) &&
167 e1ee7d5a Iustin Pop
  not (Node.failN1 node) ==>
168 e1ee7d5a Iustin Pop
      isFailure (Node.addSec node inst pdx)
169 e1ee7d5a Iustin Pop
170 e1ee7d5a Iustin Pop
-- | Check that an offline instance with reasonable disk size but
171 e1ee7d5a Iustin Pop
-- extra mem/cpu can always be added.
172 20bc5360 Iustin Pop
prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
173 20bc5360 Iustin Pop
prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
174 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
175 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
176 e1ee7d5a Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
177 e1ee7d5a Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
178 e1ee7d5a Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
179 e1ee7d5a Iustin Pop
  in case Node.addPri node inst' of
180 e1ee7d5a Iustin Pop
       Types.OpGood _ -> property True
181 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpGood, but got: " ++ show v
182 e1ee7d5a Iustin Pop
183 e1ee7d5a Iustin Pop
-- | Check that an offline instance with reasonable disk size but
184 e1ee7d5a Iustin Pop
-- extra mem/cpu can always be added.
185 20bc5360 Iustin Pop
prop_addOfflineSec :: NonNegative Int -> NonNegative Int
186 20bc5360 Iustin Pop
                   -> Types.Ndx -> Property
187 20bc5360 Iustin Pop
prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
188 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
189 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
190 e1ee7d5a Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
191 e1ee7d5a Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
192 e1ee7d5a Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu
193 e1ee7d5a Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
194 e1ee7d5a Iustin Pop
  in case Node.addSec node inst' pdx of
195 e1ee7d5a Iustin Pop
       Types.OpGood _ -> property True
196 e1ee7d5a Iustin Pop
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
197 e1ee7d5a Iustin Pop
198 e1ee7d5a Iustin Pop
-- | Checks for memory reservation changes.
199 20bc5360 Iustin Pop
prop_rMem :: Instance.Instance -> Property
200 20bc5360 Iustin Pop
prop_rMem inst =
201 e1ee7d5a Iustin Pop
  not (Instance.isOffline inst) ==>
202 e1ee7d5a Iustin Pop
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
203 e1ee7d5a Iustin Pop
  -- ab = auto_balance, nb = non-auto_balance
204 e1ee7d5a Iustin Pop
  -- we use -1 as the primary node of the instance
205 e1ee7d5a Iustin Pop
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
206 e1ee7d5a Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
207 e1ee7d5a Iustin Pop
      inst_ab = setInstanceSmallerThanNode node inst'
208 e1ee7d5a Iustin Pop
      inst_nb = inst_ab { Instance.autoBalance = False }
209 e1ee7d5a Iustin Pop
      -- now we have the two instances, identical except the
210 e1ee7d5a Iustin Pop
      -- autoBalance attribute
211 e1ee7d5a Iustin Pop
      orig_rmem = Node.rMem node
212 e1ee7d5a Iustin Pop
      inst_idx = Instance.idx inst_ab
213 e1ee7d5a Iustin Pop
      node_add_ab = Node.addSec node inst_ab (-1)
214 e1ee7d5a Iustin Pop
      node_add_nb = Node.addSec node inst_nb (-1)
215 e1ee7d5a Iustin Pop
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
216 e1ee7d5a Iustin Pop
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
217 e1ee7d5a Iustin Pop
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
218 e1ee7d5a Iustin Pop
       (Types.OpGood a_ab, Types.OpGood a_nb,
219 e1ee7d5a Iustin Pop
        Types.OpGood d_ab, Types.OpGood d_nb) ->
220 e1ee7d5a Iustin Pop
         printTestCase "Consistency checks failed" $
221 e1ee7d5a Iustin Pop
           Node.rMem a_ab >  orig_rmem &&
222 e1ee7d5a Iustin Pop
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
223 e1ee7d5a Iustin Pop
           Node.rMem a_nb == orig_rmem &&
224 e1ee7d5a Iustin Pop
           Node.rMem d_ab == orig_rmem &&
225 e1ee7d5a Iustin Pop
           Node.rMem d_nb == orig_rmem &&
226 e1ee7d5a Iustin Pop
           -- this is not related to rMem, but as good a place to
227 e1ee7d5a Iustin Pop
           -- test as any
228 e1ee7d5a Iustin Pop
           inst_idx `elem` Node.sList a_ab &&
229 e1ee7d5a Iustin Pop
           inst_idx `notElem` Node.sList d_ab
230 e1ee7d5a Iustin Pop
       x -> failTest $ "Failed to add/remove instances: " ++ show x
231 e1ee7d5a Iustin Pop
232 e1ee7d5a Iustin Pop
-- | Check mdsk setting.
233 20bc5360 Iustin Pop
prop_setMdsk :: Node.Node -> SmallRatio -> Bool
234 20bc5360 Iustin Pop
prop_setMdsk node mx =
235 e1ee7d5a Iustin Pop
  Node.loDsk node' >= 0 &&
236 e1ee7d5a Iustin Pop
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
237 e1ee7d5a Iustin Pop
  Node.availDisk node' >= 0 &&
238 e1ee7d5a Iustin Pop
  Node.availDisk node' <= Node.fDsk node' &&
239 e1ee7d5a Iustin Pop
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
240 e1ee7d5a Iustin Pop
  Node.mDsk node' == mx'
241 e1ee7d5a Iustin Pop
    where node' = Node.setMdsk node mx'
242 e1ee7d5a Iustin Pop
          SmallRatio mx' = mx
243 e1ee7d5a Iustin Pop
244 e1ee7d5a Iustin Pop
-- Check tag maps
245 20bc5360 Iustin Pop
prop_tagMaps_idempotent :: Property
246 20bc5360 Iustin Pop
prop_tagMaps_idempotent =
247 e1ee7d5a Iustin Pop
  forAll genTags $ \tags ->
248 e1ee7d5a Iustin Pop
  Node.delTags (Node.addTags m tags) tags ==? m
249 e1ee7d5a Iustin Pop
    where m = Map.empty
250 e1ee7d5a Iustin Pop
251 20bc5360 Iustin Pop
prop_tagMaps_reject :: Property
252 20bc5360 Iustin Pop
prop_tagMaps_reject =
253 e1ee7d5a Iustin Pop
  forAll (genTags `suchThat` (not . null)) $ \tags ->
254 e1ee7d5a Iustin Pop
  let m = Node.addTags Map.empty tags
255 e1ee7d5a Iustin Pop
  in all (\t -> Node.rejectAddTags m [t]) tags
256 e1ee7d5a Iustin Pop
257 20bc5360 Iustin Pop
prop_showField :: Node.Node -> Property
258 20bc5360 Iustin Pop
prop_showField node =
259 e1ee7d5a Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
260 e1ee7d5a Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
261 e1ee7d5a Iustin Pop
  Node.showField node field /= Types.unknownField
262 e1ee7d5a Iustin Pop
263 20bc5360 Iustin Pop
prop_computeGroups :: [Node.Node] -> Bool
264 20bc5360 Iustin Pop
prop_computeGroups nodes =
265 e1ee7d5a Iustin Pop
  let ng = Node.computeGroups nodes
266 e1ee7d5a Iustin Pop
      onlyuuid = map fst ng
267 e1ee7d5a Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
268 e1ee7d5a Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
269 e1ee7d5a Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
270 e1ee7d5a Iustin Pop
     (null nodes || not (null ng))
271 e1ee7d5a Iustin Pop
272 e1ee7d5a Iustin Pop
-- Check idempotence of add/remove operations
273 20bc5360 Iustin Pop
prop_addPri_idempotent :: Property
274 20bc5360 Iustin Pop
prop_addPri_idempotent =
275 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
276 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
277 e1ee7d5a Iustin Pop
  case Node.addPri node inst of
278 e1ee7d5a Iustin Pop
    Types.OpGood node' -> Node.removePri node' inst ==? node
279 e1ee7d5a Iustin Pop
    _ -> failTest "Can't add instance"
280 e1ee7d5a Iustin Pop
281 20bc5360 Iustin Pop
prop_addSec_idempotent :: Property
282 20bc5360 Iustin Pop
prop_addSec_idempotent =
283 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
284 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
285 e1ee7d5a Iustin Pop
  let pdx = Node.idx node + 1
286 e1ee7d5a Iustin Pop
      inst' = Instance.setPri inst pdx
287 e1ee7d5a Iustin Pop
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
288 e1ee7d5a Iustin Pop
  in case Node.addSec node inst'' pdx of
289 e1ee7d5a Iustin Pop
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
290 e1ee7d5a Iustin Pop
       _ -> failTest "Can't add instance"
291 e1ee7d5a Iustin Pop
292 e09c1fa0 Iustin Pop
testSuite "HTools/Node"
293 20bc5360 Iustin Pop
            [ 'prop_setAlias
294 20bc5360 Iustin Pop
            , 'prop_setOffline
295 20bc5360 Iustin Pop
            , 'prop_setMcpu
296 20bc5360 Iustin Pop
            , 'prop_setXmem
297 20bc5360 Iustin Pop
            , 'prop_addPriFM
298 20bc5360 Iustin Pop
            , 'prop_addPriFD
299 20bc5360 Iustin Pop
            , 'prop_addPriFC
300 20bc5360 Iustin Pop
            , 'prop_addSec
301 20bc5360 Iustin Pop
            , 'prop_addOfflinePri
302 20bc5360 Iustin Pop
            , 'prop_addOfflineSec
303 20bc5360 Iustin Pop
            , 'prop_rMem
304 20bc5360 Iustin Pop
            , 'prop_setMdsk
305 20bc5360 Iustin Pop
            , 'prop_tagMaps_idempotent
306 20bc5360 Iustin Pop
            , 'prop_tagMaps_reject
307 20bc5360 Iustin Pop
            , 'prop_showField
308 20bc5360 Iustin Pop
            , 'prop_computeGroups
309 20bc5360 Iustin Pop
            , 'prop_addPri_idempotent
310 20bc5360 Iustin Pop
            , 'prop_addSec_idempotent
311 e1ee7d5a Iustin Pop
            ]