Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Node.hs @ a8038349

History | View | Annotate | Download (11.2 kB)

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

    
4
{-| Unittests for ganeti-htools.
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.Node
30
  ( testHTools_Node
31
  , Node.Node(..)
32
  , setInstanceSmallerThanNode
33
  , genNode
34
  , genOnlineNode
35
  ) where
36

    
37
import Test.QuickCheck
38

    
39
import Control.Monad
40
import qualified Data.Map as Map
41
import Data.List
42

    
43
import Test.Ganeti.TestHelper
44
import Test.Ganeti.TestCommon
45
import Test.Ganeti.TestHTools
46
import Test.Ganeti.HTools.Instance (genInstanceSmallerThanNode)
47

    
48
import Ganeti.BasicTypes
49
import qualified Ganeti.HTools.Container as Container
50
import qualified Ganeti.HTools.Instance as Instance
51
import qualified Ganeti.HTools.Node as Node
52
import qualified Ganeti.HTools.Types as Types
53

    
54
-- * Arbitrary instances
55

    
56
-- | Generas an arbitrary node based on sizing information.
57
genNode :: Maybe Int -- ^ Minimum node size in terms of units
58
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
59
                     -- just by the max... constants)
60
        -> Gen Node.Node
61
genNode min_multiplier max_multiplier = do
62
  let (base_mem, base_dsk, base_cpu) =
63
        case min_multiplier of
64
          Just mm -> (mm * Types.unitMem,
65
                      mm * Types.unitDsk,
66
                      mm * Types.unitCpu)
67
          Nothing -> (0, 0, 0)
68
      (top_mem, top_dsk, top_cpu)  =
69
        case max_multiplier of
70
          Just mm -> (mm * Types.unitMem,
71
                      mm * Types.unitDsk,
72
                      mm * Types.unitCpu)
73
          Nothing -> (maxMem, maxDsk, maxCpu)
74
  name  <- getFQDN
75
  mem_t <- choose (base_mem, top_mem)
76
  mem_f <- choose (base_mem, mem_t)
77
  mem_n <- choose (0, mem_t - mem_f)
78
  dsk_t <- choose (base_dsk, top_dsk)
79
  dsk_f <- choose (base_dsk, dsk_t)
80
  cpu_t <- choose (base_cpu, top_cpu)
81
  offl  <- arbitrary
82
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
83
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
84
      n' = Node.setPolicy nullIPolicy n
85
  return $ Node.buildPeers n' Container.empty
86

    
87
-- | Helper function to generate a sane node.
88
genOnlineNode :: Gen Node.Node
89
genOnlineNode =
90
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
91
                              not (Node.failN1 n) &&
92
                              Node.availDisk n > 0 &&
93
                              Node.availMem n > 0 &&
94
                              Node.availCpu n > 0)
95

    
96
-- and a random node
97
instance Arbitrary Node.Node where
98
  arbitrary = genNode Nothing Nothing
99

    
100
-- * Test cases
101

    
102
prop_setAlias :: Node.Node -> String -> Bool
103
prop_setAlias node name =
104
  Node.name newnode == Node.name node &&
105
  Node.alias newnode == name
106
    where newnode = Node.setAlias node name
107

    
108
prop_setOffline :: Node.Node -> Bool -> Property
109
prop_setOffline node status =
110
  Node.offline newnode ==? status
111
    where newnode = Node.setOffline node status
112

    
113
prop_setXmem :: Node.Node -> Int -> Property
114
prop_setXmem node xm =
115
  Node.xMem newnode ==? xm
116
    where newnode = Node.setXmem node xm
117

    
118
prop_setMcpu :: Node.Node -> Double -> Property
119
prop_setMcpu node mc =
120
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
121
    where newnode = Node.setMcpu node mc
122

    
123
-- | Check that an instance add with too high memory or disk will be
124
-- rejected.
125
prop_addPriFM :: Node.Node -> Instance.Instance -> Property
126
prop_addPriFM node inst =
127
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
128
  not (Instance.isOffline inst) ==>
129
  case Node.addPri node inst'' of
130
    Bad Types.FailMem -> True
131
    _ -> False
132
  where inst' = setInstanceSmallerThanNode node inst
133
        inst'' = inst' { Instance.mem = Instance.mem inst }
134

    
135
-- | Check that adding a primary instance with too much disk fails
136
-- with type FailDisk.
137
prop_addPriFD :: Node.Node -> Instance.Instance -> Property
138
prop_addPriFD node inst =
139
  forAll (elements Instance.localStorageTemplates) $ \dt ->
140
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
141
  let inst' = setInstanceSmallerThanNode node inst
142
      inst'' = inst' { Instance.dsk = Instance.dsk inst
143
                     , Instance.diskTemplate = dt }
144
  in case Node.addPri node inst'' of
145
       Bad Types.FailDisk -> True
146
       _ -> False
147

    
148
-- | Check that adding a primary instance with too many VCPUs fails
149
-- with type FailCPU.
150
prop_addPriFC :: Property
151
prop_addPriFC =
152
  forAll (choose (1, maxCpu)) $ \extra ->
153
  forAll genOnlineNode $ \node ->
154
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
155
  let inst' = setInstanceSmallerThanNode node inst
156
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
157
  in case Node.addPri node inst'' of
158
       Bad Types.FailCPU -> passTest
159
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
160

    
161
-- | Check that an instance add with too high memory or disk will be
162
-- rejected.
163
prop_addSec :: Node.Node -> Instance.Instance -> Int -> Property
164
prop_addSec node inst pdx =
165
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
166
    not (Instance.isOffline inst)) ||
167
   Instance.dsk inst >= Node.fDsk node) &&
168
  not (Node.failN1 node) ==>
169
      isBad (Node.addSec node inst pdx)
170

    
171
-- | Check that an offline instance with reasonable disk size but
172
-- extra mem/cpu can always be added.
173
prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
174
prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
175
  forAll genOnlineNode $ \node ->
176
  forAll (genInstanceSmallerThanNode node) $ \inst ->
177
  let inst' = inst { Instance.runSt = Types.AdminOffline
178
                   , Instance.mem = Node.availMem node + extra_mem
179
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
180
  in case Node.addPri node inst' of
181
       Ok _ -> passTest
182
       v -> failTest $ "Expected OpGood, but got: " ++ show v
183

    
184
-- | Check that an offline instance with reasonable disk size but
185
-- extra mem/cpu can always be added.
186
prop_addOfflineSec :: NonNegative Int -> NonNegative Int
187
                   -> Types.Ndx -> Property
188
prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
189
  forAll genOnlineNode $ \node ->
190
  forAll (genInstanceSmallerThanNode node) $ \inst ->
191
  let inst' = inst { Instance.runSt = Types.AdminOffline
192
                   , Instance.mem = Node.availMem node + extra_mem
193
                   , Instance.vcpus = Node.availCpu node + extra_cpu
194
                   , Instance.diskTemplate = Types.DTDrbd8 }
195
  in case Node.addSec node inst' pdx of
196
       Ok _ -> passTest
197
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
198

    
199
-- | Checks for memory reservation changes.
200
prop_rMem :: Instance.Instance -> Property
201
prop_rMem inst =
202
  not (Instance.isOffline inst) ==>
203
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
204
  -- ab = auto_balance, nb = non-auto_balance
205
  -- we use -1 as the primary node of the instance
206
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
207
                   , Instance.diskTemplate = Types.DTDrbd8 }
208
      inst_ab = setInstanceSmallerThanNode node inst'
209
      inst_nb = inst_ab { Instance.autoBalance = False }
210
      -- now we have the two instances, identical except the
211
      -- autoBalance attribute
212
      orig_rmem = Node.rMem node
213
      inst_idx = Instance.idx inst_ab
214
      node_add_ab = Node.addSec node inst_ab (-1)
215
      node_add_nb = Node.addSec node inst_nb (-1)
216
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
217
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
218
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
219
       (Ok a_ab, Ok a_nb,
220
        Ok d_ab, Ok d_nb) ->
221
         printTestCase "Consistency checks failed" $
222
           Node.rMem a_ab >  orig_rmem &&
223
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
224
           Node.rMem a_nb == orig_rmem &&
225
           Node.rMem d_ab == orig_rmem &&
226
           Node.rMem d_nb == orig_rmem &&
227
           -- this is not related to rMem, but as good a place to
228
           -- test as any
229
           inst_idx `elem` Node.sList a_ab &&
230
           inst_idx `notElem` Node.sList d_ab
231
       x -> failTest $ "Failed to add/remove instances: " ++ show x
232

    
233
-- | Check mdsk setting.
234
prop_setMdsk :: Node.Node -> SmallRatio -> Bool
235
prop_setMdsk node mx =
236
  Node.loDsk node' >= 0 &&
237
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
238
  Node.availDisk node' >= 0 &&
239
  Node.availDisk node' <= Node.fDsk node' &&
240
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
241
  Node.mDsk node' == mx'
242
    where node' = Node.setMdsk node mx'
243
          SmallRatio mx' = mx
244

    
245
-- Check tag maps
246
prop_tagMaps_idempotent :: Property
247
prop_tagMaps_idempotent =
248
  forAll genTags $ \tags ->
249
  Node.delTags (Node.addTags m tags) tags ==? m
250
    where m = Map.empty
251

    
252
prop_tagMaps_reject :: Property
253
prop_tagMaps_reject =
254
  forAll (genTags `suchThat` (not . null)) $ \tags ->
255
  let m = Node.addTags Map.empty tags
256
  in all (\t -> Node.rejectAddTags m [t]) tags
257

    
258
prop_showField :: Node.Node -> Property
259
prop_showField node =
260
  forAll (elements Node.defaultFields) $ \ field ->
261
  fst (Node.showHeader field) /= Types.unknownField &&
262
  Node.showField node field /= Types.unknownField
263

    
264
prop_computeGroups :: [Node.Node] -> Bool
265
prop_computeGroups nodes =
266
  let ng = Node.computeGroups nodes
267
      onlyuuid = map fst ng
268
  in length nodes == sum (map (length . snd) ng) &&
269
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
270
     length (nub onlyuuid) == length onlyuuid &&
271
     (null nodes || not (null ng))
272

    
273
-- Check idempotence of add/remove operations
274
prop_addPri_idempotent :: Property
275
prop_addPri_idempotent =
276
  forAll genOnlineNode $ \node ->
277
  forAll (genInstanceSmallerThanNode node) $ \inst ->
278
  case Node.addPri node inst of
279
    Ok node' -> Node.removePri node' inst ==? node
280
    _ -> failTest "Can't add instance"
281

    
282
prop_addSec_idempotent :: Property
283
prop_addSec_idempotent =
284
  forAll genOnlineNode $ \node ->
285
  forAll (genInstanceSmallerThanNode node) $ \inst ->
286
  let pdx = Node.idx node + 1
287
      inst' = Instance.setPri inst pdx
288
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
289
  in case Node.addSec node inst'' pdx of
290
       Ok node' -> Node.removeSec node' inst'' ==? node
291
       _ -> failTest "Can't add instance"
292

    
293
testSuite "HTools/Node"
294
            [ 'prop_setAlias
295
            , 'prop_setOffline
296
            , 'prop_setMcpu
297
            , 'prop_setXmem
298
            , 'prop_addPriFM
299
            , 'prop_addPriFD
300
            , 'prop_addPriFC
301
            , 'prop_addSec
302
            , 'prop_addOfflinePri
303
            , 'prop_addOfflineSec
304
            , 'prop_rMem
305
            , 'prop_setMdsk
306
            , 'prop_tagMaps_idempotent
307
            , 'prop_tagMaps_reject
308
            , 'prop_showField
309
            , 'prop_computeGroups
310
            , 'prop_addPri_idempotent
311
            , 'prop_addSec_idempotent
312
            ]