Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Node.hs @ 5b11f8db

History | View | Annotate | Download (11.3 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 qualified Ganeti.HTools.Container as Container
49
import qualified Ganeti.HTools.Instance as Instance
50
import qualified Ganeti.HTools.Node as Node
51
import qualified Ganeti.HTools.Types as Types
52

    
53
-- * Arbitrary instances
54

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

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

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

    
99
-- * Test cases
100

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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