Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ bcd17bf0

History | View | Annotate | Download (47.6 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittests for ganeti-htools.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.HTools.QC
29
  ( testUtils
30
  , testPeerMap
31
  , testContainer
32
  , testInstance
33
  , testNode
34
  , testText
35
  , testOpCodes
36
  , testJobs
37
  , testCluster
38
  , testLoader
39
  , testTypes
40
  ) where
41

    
42
import Test.QuickCheck
43
import Data.List (findIndex, intercalate, nub, isPrefixOf)
44
import Data.Maybe
45
import Control.Monad
46
import qualified Text.JSON as J
47
import qualified Data.Map
48
import qualified Data.IntMap as IntMap
49
import qualified Ganeti.OpCodes as OpCodes
50
import qualified Ganeti.Jobs as Jobs
51
import qualified Ganeti.Luxi
52
import qualified Ganeti.HTools.CLI as CLI
53
import qualified Ganeti.HTools.Cluster as Cluster
54
import qualified Ganeti.HTools.Container as Container
55
import qualified Ganeti.HTools.ExtLoader
56
import qualified Ganeti.HTools.IAlloc as IAlloc
57
import qualified Ganeti.HTools.Instance as Instance
58
import qualified Ganeti.HTools.JSON as JSON
59
import qualified Ganeti.HTools.Loader as Loader
60
import qualified Ganeti.HTools.Luxi
61
import qualified Ganeti.HTools.Node as Node
62
import qualified Ganeti.HTools.Group as Group
63
import qualified Ganeti.HTools.PeerMap as PeerMap
64
import qualified Ganeti.HTools.Rapi
65
import qualified Ganeti.HTools.Simu
66
import qualified Ganeti.HTools.Text as Text
67
import qualified Ganeti.HTools.Types as Types
68
import qualified Ganeti.HTools.Utils as Utils
69
import qualified Ganeti.HTools.Version
70
import qualified Ganeti.Constants as C
71

    
72
import qualified Ganeti.HTools.Program.Hail
73
import qualified Ganeti.HTools.Program.Hbal
74
import qualified Ganeti.HTools.Program.Hscan
75
import qualified Ganeti.HTools.Program.Hspace
76

    
77
import Ganeti.HTools.QCHelper (testSuite)
78

    
79
-- * Constants
80

    
81
-- | Maximum memory (1TiB, somewhat random value).
82
maxMem :: Int
83
maxMem = 1024 * 1024
84

    
85
-- | Maximum disk (8TiB, somewhat random value).
86
maxDsk :: Int
87
maxDsk = 1024 * 1024 * 8
88

    
89
-- | Max CPUs (1024, somewhat random value).
90
maxCpu :: Int
91
maxCpu = 1024
92

    
93
-- | Null iPolicy, and by null we mean very liberal.
94
nullIPolicy = Types.IPolicy
95
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
96
                                       , Types.iSpecCpuCount   = 0
97
                                       , Types.iSpecDiskSize   = 0
98
                                       , Types.iSpecDiskCount  = 0
99
                                       , Types.iSpecNicCount   = 0
100
                                       }
101
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
102
                                       , Types.iSpecCpuCount   = maxBound
103
                                       , Types.iSpecDiskSize   = maxBound
104
                                       , Types.iSpecDiskCount  = C.maxDisks
105
                                       , Types.iSpecNicCount   = C.maxNics
106
                                       }
107
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
108
                                       , Types.iSpecCpuCount   = Types.unitCpu
109
                                       , Types.iSpecDiskSize   = Types.unitDsk
110
                                       , Types.iSpecDiskCount  = 1
111
                                       , Types.iSpecNicCount   = 1
112
                                       }
113
  , Types.iPolicyDiskTemplates = [Types.DTDrbd8, Types.DTPlain]
114
  }
115

    
116

    
117
defGroup :: Group.Group
118
defGroup = flip Group.setIdx 0 $
119
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
120
                  nullIPolicy
121

    
122
defGroupList :: Group.List
123
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
124

    
125
defGroupAssoc :: Data.Map.Map String Types.Gdx
126
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
127

    
128
-- * Helper functions
129

    
130
-- | Simple checker for whether OpResult is fail or pass.
131
isFailure :: Types.OpResult a -> Bool
132
isFailure (Types.OpFail _) = True
133
isFailure _ = False
134

    
135
-- | Checks for equality with proper annotation.
136
(==?) :: (Show a, Eq a) => a -> a -> Property
137
(==?) x y = printTestCase
138
            ("Expected equality, but '" ++
139
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
140
infix 3 ==?
141

    
142
-- | Update an instance to be smaller than a node.
143
setInstanceSmallerThanNode node inst =
144
  inst { Instance.mem = Node.availMem node `div` 2
145
       , Instance.dsk = Node.availDisk node `div` 2
146
       , Instance.vcpus = Node.availCpu node `div` 2
147
       }
148

    
149
-- | Check if an instance is smaller than a node.
150
isInstanceSmallerThanNode node inst =
151
  Instance.mem inst   <= Node.availMem node `div` 2 &&
152
  Instance.dsk inst   <= Node.availDisk node `div` 2 &&
153
  Instance.vcpus inst <= Node.availCpu node `div` 2
154

    
155
-- | Create an instance given its spec.
156
createInstance mem dsk vcpus =
157
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
158
    Types.DTDrbd8
159

    
160
-- | Create a small cluster by repeating a node spec.
161
makeSmallCluster :: Node.Node -> Int -> Node.List
162
makeSmallCluster node count =
163
  let origname = Node.name node
164
      origalias = Node.alias node
165
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
166
                                , Node.alias = origalias ++ "-" ++ show idx })
167
              [1..count]
168
      fn = flip Node.buildPeers Container.empty
169
      namelst = map (\n -> (Node.name n, fn n)) nodes
170
      (_, nlst) = Loader.assignIndices namelst
171
  in nlst
172

    
173
-- | Make a small cluster, both nodes and instances.
174
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
175
                      -> (Node.List, Instance.List, Instance.Instance)
176
makeSmallEmptyCluster node count inst =
177
  (makeSmallCluster node count, Container.empty,
178
   setInstanceSmallerThanNode node inst)
179

    
180
-- | Checks if a node is "big" enough.
181
isNodeBig :: Int -> Node.Node -> Bool
182
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
183
                      && Node.availMem node > size * Types.unitMem
184
                      && Node.availCpu node > size * Types.unitCpu
185

    
186
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
187
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
188

    
189
-- | Assigns a new fresh instance to a cluster; this is not
190
-- allocation, so no resource checks are done.
191
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
192
                  Types.Idx -> Types.Idx ->
193
                  (Node.List, Instance.List)
194
assignInstance nl il inst pdx sdx =
195
  let pnode = Container.find pdx nl
196
      snode = Container.find sdx nl
197
      maxiidx = if Container.null il
198
                  then 0
199
                  else fst (Container.findMax il) + 1
200
      inst' = inst { Instance.idx = maxiidx,
201
                     Instance.pNode = pdx, Instance.sNode = sdx }
202
      pnode' = Node.setPri pnode inst'
203
      snode' = Node.setSec snode inst'
204
      nl' = Container.addTwo pdx pnode' sdx snode' nl
205
      il' = Container.add maxiidx inst' il
206
  in (nl', il')
207

    
208
-- * Arbitrary instances
209

    
210
-- | Defines a DNS name.
211
newtype DNSChar = DNSChar { dnsGetChar::Char }
212

    
213
instance Arbitrary DNSChar where
214
  arbitrary = do
215
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
216
    return (DNSChar x)
217

    
218
getName :: Gen String
219
getName = do
220
  n <- choose (1, 64)
221
  dn <- vector n::Gen [DNSChar]
222
  return (map dnsGetChar dn)
223

    
224
getFQDN :: Gen String
225
getFQDN = do
226
  felem <- getName
227
  ncomps <- choose (1, 4)
228
  frest <- vector ncomps::Gen [[DNSChar]]
229
  let frest' = map (map dnsGetChar) frest
230
  return (felem ++ "." ++ intercalate "." frest')
231

    
232
-- | Defines a tag type.
233
newtype TagChar = TagChar { tagGetChar :: Char }
234

    
235
-- | All valid tag chars. This doesn't need to match _exactly_
236
-- Ganeti's own tag regex, just enough for it to be close.
237
tagChar :: [Char]
238
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
239

    
240
instance Arbitrary TagChar where
241
  arbitrary = do
242
    c <- elements tagChar
243
    return (TagChar c)
244

    
245
-- | Generates a tag
246
genTag :: Gen [TagChar]
247
genTag = do
248
  -- the correct value would be C.maxTagLen, but that's way too
249
  -- verbose in unittests, and at the moment I don't see any possible
250
  -- bugs with longer tags and the way we use tags in htools
251
  n <- choose (1, 10)
252
  vector n
253

    
254
-- | Generates a list of tags (correctly upper bounded).
255
genTags :: Gen [String]
256
genTags = do
257
  -- the correct value would be C.maxTagsPerObj, but per the comment
258
  -- in genTag, we don't use tags enough in htools to warrant testing
259
  -- such big values
260
  n <- choose (0, 10::Int)
261
  tags <- mapM (const genTag) [1..n]
262
  return $ map (map tagGetChar) tags
263

    
264
instance Arbitrary Types.InstanceStatus where
265
    arbitrary = elements [minBound..maxBound]
266

    
267
-- let's generate a random instance
268
instance Arbitrary Instance.Instance where
269
  arbitrary = do
270
    name <- getFQDN
271
    mem <- choose (0, maxMem)
272
    dsk <- choose (0, maxDsk)
273
    run_st <- arbitrary
274
    pn <- arbitrary
275
    sn <- arbitrary
276
    vcpus <- choose (0, maxCpu)
277
    return $ Instance.create name mem dsk vcpus run_st [] True pn sn
278
              Types.DTDrbd8
279

    
280
-- | Generas an arbitrary node based on sizing information.
281
genNode :: Maybe Int -- ^ Minimum node size in terms of units
282
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
283
                     -- just by the max... constants)
284
        -> Gen Node.Node
285
genNode min_multiplier max_multiplier = do
286
  let (base_mem, base_dsk, base_cpu) =
287
        case min_multiplier of
288
          Just mm -> (mm * Types.unitMem,
289
                      mm * Types.unitDsk,
290
                      mm * Types.unitCpu)
291
          Nothing -> (0, 0, 0)
292
      (top_mem, top_dsk, top_cpu)  =
293
        case max_multiplier of
294
          Just mm -> (mm * Types.unitMem,
295
                      mm * Types.unitDsk,
296
                      mm * Types.unitCpu)
297
          Nothing -> (maxMem, maxDsk, maxCpu)
298
  name  <- getFQDN
299
  mem_t <- choose (base_mem, top_mem)
300
  mem_f <- choose (base_mem, mem_t)
301
  mem_n <- choose (0, mem_t - mem_f)
302
  dsk_t <- choose (base_dsk, top_dsk)
303
  dsk_f <- choose (base_dsk, dsk_t)
304
  cpu_t <- choose (base_cpu, top_cpu)
305
  offl  <- arbitrary
306
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
307
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 0
308
      n' = Node.setPolicy nullIPolicy n
309
  return $ Node.buildPeers n' Container.empty
310

    
311
-- | Helper function to generate a sane node.
312
genOnlineNode :: Gen Node.Node
313
genOnlineNode = do
314
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
315
                              not (Node.failN1 n) &&
316
                              Node.availDisk n > 0 &&
317
                              Node.availMem n > 0 &&
318
                              Node.availCpu n > 0)
319

    
320
-- and a random node
321
instance Arbitrary Node.Node where
322
  arbitrary = genNode Nothing Nothing
323

    
324
-- replace disks
325
instance Arbitrary OpCodes.ReplaceDisksMode where
326
  arbitrary = elements [minBound..maxBound]
327

    
328
instance Arbitrary OpCodes.OpCode where
329
  arbitrary = do
330
    op_id <- elements [ "OP_TEST_DELAY"
331
                      , "OP_INSTANCE_REPLACE_DISKS"
332
                      , "OP_INSTANCE_FAILOVER"
333
                      , "OP_INSTANCE_MIGRATE"
334
                      ]
335
    case op_id of
336
      "OP_TEST_DELAY" ->
337
        liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
338
      "OP_INSTANCE_REPLACE_DISKS" ->
339
        liftM5 OpCodes.OpInstanceReplaceDisks arbitrary arbitrary
340
          arbitrary arbitrary arbitrary
341
      "OP_INSTANCE_FAILOVER" ->
342
        liftM3 OpCodes.OpInstanceFailover arbitrary arbitrary
343
          arbitrary
344
      "OP_INSTANCE_MIGRATE" ->
345
        liftM5 OpCodes.OpInstanceMigrate arbitrary arbitrary
346
          arbitrary arbitrary arbitrary
347
      _ -> fail "Wrong opcode"
348

    
349
instance Arbitrary Jobs.OpStatus where
350
  arbitrary = elements [minBound..maxBound]
351

    
352
instance Arbitrary Jobs.JobStatus where
353
  arbitrary = elements [minBound..maxBound]
354

    
355
newtype SmallRatio = SmallRatio Double deriving Show
356
instance Arbitrary SmallRatio where
357
  arbitrary = do
358
    v <- choose (0, 1)
359
    return $ SmallRatio v
360

    
361
instance Arbitrary Types.AllocPolicy where
362
  arbitrary = elements [minBound..maxBound]
363

    
364
instance Arbitrary Types.DiskTemplate where
365
  arbitrary = elements [minBound..maxBound]
366

    
367
instance Arbitrary Types.FailMode where
368
  arbitrary = elements [minBound..maxBound]
369

    
370
instance Arbitrary a => Arbitrary (Types.OpResult a) where
371
  arbitrary = arbitrary >>= \c ->
372
              if c
373
                then liftM Types.OpGood arbitrary
374
                else liftM Types.OpFail arbitrary
375

    
376
instance Arbitrary Types.ISpec where
377
  arbitrary = do
378
    mem <- arbitrary::Gen (NonNegative Int)
379
    dsk_c <- arbitrary::Gen (NonNegative Int)
380
    dsk_s <- arbitrary::Gen (NonNegative Int)
381
    cpu <- arbitrary::Gen (NonNegative Int)
382
    nic <- arbitrary::Gen (NonNegative Int)
383
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem
384
                       , Types.iSpecCpuCount   = fromIntegral cpu
385
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
386
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
387
                       , Types.iSpecNicCount   = fromIntegral nic
388
                       }
389

    
390
-- | Helper function to check whether a spec is LTE than another
391
iSpecSmaller :: Types.ISpec -> Types.ISpec -> Bool
392
iSpecSmaller imin imax =
393
  Types.iSpecMemorySize imin <= Types.iSpecMemorySize imax &&
394
  Types.iSpecCpuCount imin   <= Types.iSpecCpuCount imax &&
395
  Types.iSpecDiskSize imin   <= Types.iSpecDiskSize imax &&
396
  Types.iSpecDiskCount imin  <= Types.iSpecDiskCount imax &&
397
  Types.iSpecNicCount imin   <= Types.iSpecNicCount imax
398

    
399
instance Arbitrary Types.IPolicy where
400
  arbitrary = do
401
    imin <- arbitrary
402
    istd <- arbitrary `suchThat` (iSpecSmaller imin)
403
    imax <- arbitrary `suchThat` (iSpecSmaller istd)
404
    dts  <- arbitrary
405
    return Types.IPolicy { Types.iPolicyMinSpec = imin
406
                         , Types.iPolicyStdSpec = istd
407
                         , Types.iPolicyMaxSpec = imax
408
                         , Types.iPolicyDiskTemplates = dts
409
                         }
410

    
411
-- * Actual tests
412

    
413
-- ** Utils tests
414

    
415
-- | If the list is not just an empty element, and if the elements do
416
-- not contain commas, then join+split should be idempotent.
417
prop_Utils_commaJoinSplit =
418
  forAll (arbitrary `suchThat`
419
          (\l -> l /= [""] && all (notElem ',') l )) $ \lst ->
420
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
421

    
422
-- | Split and join should always be idempotent.
423
prop_Utils_commaSplitJoin s =
424
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
425

    
426
-- | fromObjWithDefault, we test using the Maybe monad and an integer
427
-- value.
428
prop_Utils_fromObjWithDefault def_value random_key =
429
  -- a missing key will be returned with the default
430
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
431
  -- a found key will be returned as is, not with default
432
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
433
       random_key (def_value+1) == Just def_value
434
    where _types = def_value :: Integer
435

    
436
-- | Test that functional if' behaves like the syntactic sugar if.
437
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
438
prop_Utils_if'if cnd a b =
439
  Utils.if' cnd a b ==? if cnd then a else b
440

    
441
-- | Test basic select functionality
442
prop_Utils_select :: Int      -- ^ Default result
443
                  -> [Int]    -- ^ List of False values
444
                  -> [Int]    -- ^ List of True values
445
                  -> Gen Prop -- ^ Test result
446
prop_Utils_select def lst1 lst2 =
447
  Utils.select def (flist ++ tlist) ==? expectedresult
448
    where expectedresult = Utils.if' (null lst2) def (head lst2)
449
          flist = zip (repeat False) lst1
450
          tlist = zip (repeat True)  lst2
451

    
452
-- | Test basic select functionality with undefined default
453
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
454
                         -> NonEmptyList Int -- ^ List of True values
455
                         -> Gen Prop         -- ^ Test result
456
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
457
  Utils.select undefined (flist ++ tlist) ==? head lst2
458
    where flist = zip (repeat False) lst1
459
          tlist = zip (repeat True)  lst2
460

    
461
-- | Test basic select functionality with undefined list values
462
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
463
                         -> NonEmptyList Int -- ^ List of True values
464
                         -> Gen Prop         -- ^ Test result
465
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
466
  Utils.select undefined cndlist ==? head lst2
467
    where flist = zip (repeat False) lst1
468
          tlist = zip (repeat True)  lst2
469
          cndlist = flist ++ tlist ++ [undefined]
470

    
471
prop_Utils_parseUnit (NonNegative n) =
472
  Utils.parseUnit (show n) == Types.Ok n &&
473
  Utils.parseUnit (show n ++ "m") == Types.Ok n &&
474
  (case Utils.parseUnit (show n ++ "M") of
475
     Types.Ok m -> if n > 0
476
                     then m < n  -- for positive values, X MB is < than X MiB
477
                     else m == 0 -- but for 0, 0 MB == 0 MiB
478
     Types.Bad _ -> False) &&
479
  Utils.parseUnit (show n ++ "g") == Types.Ok (n*1024) &&
480
  Utils.parseUnit (show n ++ "t") == Types.Ok (n*1048576) &&
481
  Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int)
482
    where _types = n::Int
483

    
484
-- | Test list for the Utils module.
485
testSuite "Utils"
486
            [ 'prop_Utils_commaJoinSplit
487
            , 'prop_Utils_commaSplitJoin
488
            , 'prop_Utils_fromObjWithDefault
489
            , 'prop_Utils_if'if
490
            , 'prop_Utils_select
491
            , 'prop_Utils_select_undefd
492
            , 'prop_Utils_select_undefv
493
            , 'prop_Utils_parseUnit
494
            ]
495

    
496
-- ** PeerMap tests
497

    
498
-- | Make sure add is idempotent.
499
prop_PeerMap_addIdempotent pmap key em =
500
  fn puniq ==? fn (fn puniq)
501
    where _types = (pmap::PeerMap.PeerMap,
502
                    key::PeerMap.Key, em::PeerMap.Elem)
503
          fn = PeerMap.add key em
504
          puniq = PeerMap.accumArray const pmap
505

    
506
-- | Make sure remove is idempotent.
507
prop_PeerMap_removeIdempotent pmap key =
508
  fn puniq ==? fn (fn puniq)
509
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
510
          fn = PeerMap.remove key
511
          puniq = PeerMap.accumArray const pmap
512

    
513
-- | Make sure a missing item returns 0.
514
prop_PeerMap_findMissing pmap key =
515
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
516
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
517
          puniq = PeerMap.accumArray const pmap
518

    
519
-- | Make sure an added item is found.
520
prop_PeerMap_addFind pmap key em =
521
  PeerMap.find key (PeerMap.add key em puniq) ==? em
522
    where _types = (pmap::PeerMap.PeerMap,
523
                    key::PeerMap.Key, em::PeerMap.Elem)
524
          puniq = PeerMap.accumArray const pmap
525

    
526
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
527
prop_PeerMap_maxElem pmap =
528
  PeerMap.maxElem puniq ==? if null puniq then 0
529
                              else (maximum . snd . unzip) puniq
530
    where _types = pmap::PeerMap.PeerMap
531
          puniq = PeerMap.accumArray const pmap
532

    
533
-- | List of tests for the PeerMap module.
534
testSuite "PeerMap"
535
            [ 'prop_PeerMap_addIdempotent
536
            , 'prop_PeerMap_removeIdempotent
537
            , 'prop_PeerMap_maxElem
538
            , 'prop_PeerMap_addFind
539
            , 'prop_PeerMap_findMissing
540
            ]
541

    
542
-- ** Container tests
543

    
544
-- we silence the following due to hlint bug fixed in later versions
545
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
546
prop_Container_addTwo cdata i1 i2 =
547
  fn i1 i2 cont == fn i2 i1 cont &&
548
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
549
    where _types = (cdata::[Int],
550
                    i1::Int, i2::Int)
551
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
552
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
553

    
554
prop_Container_nameOf node =
555
  let nl = makeSmallCluster node 1
556
      fnode = head (Container.elems nl)
557
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
558

    
559
-- | We test that in a cluster, given a random node, we can find it by
560
-- its name and alias, as long as all names and aliases are unique,
561
-- and that we fail to find a non-existing name.
562
prop_Container_findByName node othername =
563
  forAll (choose (1, 20)) $ \ cnt ->
564
  forAll (choose (0, cnt - 1)) $ \ fidx ->
565
  forAll (vector cnt) $ \ names ->
566
  (length . nub) (map fst names ++ map snd names) ==
567
  length names * 2 &&
568
  othername `notElem` (map fst names ++ map snd names) ==>
569
  let nl = makeSmallCluster node cnt
570
      nodes = Container.elems nl
571
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
572
                                             nn { Node.name = name,
573
                                                  Node.alias = alias }))
574
               $ zip names nodes
575
      nl' = Container.fromList nodes'
576
      target = snd (nodes' !! fidx)
577
  in Container.findByName nl' (Node.name target) == Just target &&
578
     Container.findByName nl' (Node.alias target) == Just target &&
579
     isNothing (Container.findByName nl' othername)
580

    
581
testSuite "Container"
582
            [ 'prop_Container_addTwo
583
            , 'prop_Container_nameOf
584
            , 'prop_Container_findByName
585
            ]
586

    
587
-- ** Instance tests
588

    
589
-- Simple instance tests, we only have setter/getters
590

    
591
prop_Instance_creat inst =
592
  Instance.name inst ==? Instance.alias inst
593

    
594
prop_Instance_setIdx inst idx =
595
  Instance.idx (Instance.setIdx inst idx) ==? idx
596
    where _types = (inst::Instance.Instance, idx::Types.Idx)
597

    
598
prop_Instance_setName inst name =
599
  Instance.name newinst == name &&
600
  Instance.alias newinst == name
601
    where _types = (inst::Instance.Instance, name::String)
602
          newinst = Instance.setName inst name
603

    
604
prop_Instance_setAlias inst name =
605
  Instance.name newinst == Instance.name inst &&
606
  Instance.alias newinst == name
607
    where _types = (inst::Instance.Instance, name::String)
608
          newinst = Instance.setAlias inst name
609

    
610
prop_Instance_setPri inst pdx =
611
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
612
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
613

    
614
prop_Instance_setSec inst sdx =
615
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
616
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
617

    
618
prop_Instance_setBoth inst pdx sdx =
619
  Instance.pNode si == pdx && Instance.sNode si == sdx
620
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
621
          si = Instance.setBoth inst pdx sdx
622

    
623
prop_Instance_shrinkMG inst =
624
  Instance.mem inst >= 2 * Types.unitMem ==>
625
    case Instance.shrinkByType inst Types.FailMem of
626
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
627
      _ -> False
628

    
629
prop_Instance_shrinkMF inst =
630
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
631
    let inst' = inst { Instance.mem = mem}
632
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
633

    
634
prop_Instance_shrinkCG inst =
635
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
636
    case Instance.shrinkByType inst Types.FailCPU of
637
      Types.Ok inst' ->
638
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
639
      _ -> False
640

    
641
prop_Instance_shrinkCF inst =
642
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
643
    let inst' = inst { Instance.vcpus = vcpus }
644
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
645

    
646
prop_Instance_shrinkDG inst =
647
  Instance.dsk inst >= 2 * Types.unitDsk ==>
648
    case Instance.shrinkByType inst Types.FailDisk of
649
      Types.Ok inst' ->
650
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
651
      _ -> False
652

    
653
prop_Instance_shrinkDF inst =
654
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
655
    let inst' = inst { Instance.dsk = dsk }
656
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
657

    
658
prop_Instance_setMovable inst m =
659
  Instance.movable inst' ==? m
660
    where inst' = Instance.setMovable inst m
661

    
662
testSuite "Instance"
663
            [ 'prop_Instance_creat
664
            , 'prop_Instance_setIdx
665
            , 'prop_Instance_setName
666
            , 'prop_Instance_setAlias
667
            , 'prop_Instance_setPri
668
            , 'prop_Instance_setSec
669
            , 'prop_Instance_setBoth
670
            , 'prop_Instance_shrinkMG
671
            , 'prop_Instance_shrinkMF
672
            , 'prop_Instance_shrinkCG
673
            , 'prop_Instance_shrinkCF
674
            , 'prop_Instance_shrinkDG
675
            , 'prop_Instance_shrinkDF
676
            , 'prop_Instance_setMovable
677
            ]
678

    
679
-- ** Text backend tests
680

    
681
-- Instance text loader tests
682

    
683
prop_Text_Load_Instance name mem dsk vcpus status
684
                        (NonEmpty pnode) snode
685
                        (NonNegative pdx) (NonNegative sdx) autobal dt =
686
  pnode /= snode && pdx /= sdx ==>
687
  let vcpus_s = show vcpus
688
      dsk_s = show dsk
689
      mem_s = show mem
690
      status_s = Types.instanceStatusToRaw status
691
      ndx = if null snode
692
              then [(pnode, pdx)]
693
              else [(pnode, pdx), (snode, sdx)]
694
      nl = Data.Map.fromList ndx
695
      tags = ""
696
      sbal = if autobal then "Y" else "N"
697
      sdt = Types.diskTemplateToRaw dt
698
      inst = Text.loadInst nl
699
             [name, mem_s, dsk_s, vcpus_s, status_s,
700
              sbal, pnode, snode, sdt, tags]
701
      fail1 = Text.loadInst nl
702
              [name, mem_s, dsk_s, vcpus_s, status_s,
703
               sbal, pnode, pnode, tags]
704
      _types = ( name::String, mem::Int, dsk::Int
705
               , vcpus::Int, status::Types.InstanceStatus
706
               , snode::String
707
               , autobal::Bool)
708
  in case inst of
709
       Types.Bad msg -> printTestCase ("Failed to load instance: " ++ msg)
710
                        False
711
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
712
                                        \ loading the instance" $
713
               Instance.name i == name &&
714
               Instance.vcpus i == vcpus &&
715
               Instance.mem i == mem &&
716
               Instance.pNode i == pdx &&
717
               Instance.sNode i == (if null snode
718
                                      then Node.noSecondary
719
                                      else sdx) &&
720
               Instance.autoBalance i == autobal &&
721
               Types.isBad fail1
722

    
723
prop_Text_Load_InstanceFail ktn fields =
724
  length fields /= 10 ==>
725
    case Text.loadInst nl fields of
726
      Types.Ok _ -> printTestCase "Managed to load instance from invalid\
727
                                  \ data" False
728
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
729
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
730
    where nl = Data.Map.fromList ktn
731

    
732
prop_Text_Load_Node name tm nm fm td fd tc fo =
733
  let conv v = if v < 0
734
                 then "?"
735
                 else show v
736
      tm_s = conv tm
737
      nm_s = conv nm
738
      fm_s = conv fm
739
      td_s = conv td
740
      fd_s = conv fd
741
      tc_s = conv tc
742
      fo_s = if fo
743
               then "Y"
744
               else "N"
745
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
746
      gid = Group.uuid defGroup
747
  in case Text.loadNode defGroupAssoc
748
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
749
       Nothing -> False
750
       Just (name', node) ->
751
         if fo || any_broken
752
           then Node.offline node
753
           else Node.name node == name' && name' == name &&
754
                Node.alias node == name &&
755
                Node.tMem node == fromIntegral tm &&
756
                Node.nMem node == nm &&
757
                Node.fMem node == fm &&
758
                Node.tDsk node == fromIntegral td &&
759
                Node.fDsk node == fd &&
760
                Node.tCpu node == fromIntegral tc
761

    
762
prop_Text_Load_NodeFail fields =
763
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
764

    
765
prop_Text_NodeLSIdempotent node =
766
  (Text.loadNode defGroupAssoc.
767
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==
768
  Just (Node.name n, n)
769
    -- override failN1 to what loadNode returns by default
770
    where n = node { Node.failN1 = True, Node.offline = False
771
                   , Node.iPolicy = Types.defIPolicy }
772

    
773
prop_Text_ISpecIdempotent ispec =
774
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
775
       Text.serializeISpec $ ispec of
776
    Types.Bad msg -> printTestCase ("Failed to load ispec: " ++ msg) False
777
    Types.Ok ispec' -> ispec ==? ispec'
778

    
779
prop_Text_IPolicyIdempotent ipol =
780
  case Text.loadIPolicy . Utils.sepSplit '|' $
781
       Text.serializeIPolicy owner ipol of
782
    Types.Bad msg -> printTestCase ("Failed to load ispec: " ++ msg) False
783
    Types.Ok res -> (owner, ipol) ==? res
784
  where owner = "dummy"
785

    
786
-- | This property, while being in the text tests, does more than just
787
-- test end-to-end the serialisation and loading back workflow; it
788
-- also tests the Loader.mergeData and the actuall
789
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
790
-- allocations, not for the business logic). As such, it's a quite
791
-- complex and slow test, and that's the reason we restrict it to
792
-- small cluster sizes.
793
prop_Text_CreateSerialise =
794
  forAll genTags $ \ctags ->
795
  forAll (choose (1, 2)) $ \reqnodes ->
796
  forAll (choose (1, 20)) $ \maxiter ->
797
  forAll (choose (2, 10)) $ \count ->
798
  forAll genOnlineNode $ \node ->
799
  forAll (arbitrary `suchThat` isInstanceSmallerThanNode node) $ \inst ->
800
  let inst' = Instance.setMovable inst $ Utils.if' (reqnodes == 2) True False
801
      nl = makeSmallCluster node count
802
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
803
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst' allocn [] []
804
     of
805
       Types.Bad msg -> printTestCase ("Failed to allocate: " ++ msg) False
806
       Types.Ok (_, _, _, [], _) -> printTestCase
807
                                    "Failed to allocate: no allocations" False
808
       Types.Ok (_, nl', il', _, _) ->
809
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
810
                     Types.defIPolicy
811
             saved = Text.serializeCluster cdata
812
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
813
              Types.Bad msg -> printTestCase ("Failed to load/merge: " ++
814
                                              msg) False
815
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
816
                ctags ==? ctags2 .&&.
817
                Types.defIPolicy ==? cpol2 .&&.
818
                il' ==? il2 .&&.
819
                defGroupList ==? gl2 .&&.
820
                nl' ==? nl2
821

    
822
testSuite "Text"
823
            [ 'prop_Text_Load_Instance
824
            , 'prop_Text_Load_InstanceFail
825
            , 'prop_Text_Load_Node
826
            , 'prop_Text_Load_NodeFail
827
            , 'prop_Text_NodeLSIdempotent
828
            , 'prop_Text_ISpecIdempotent
829
            , 'prop_Text_IPolicyIdempotent
830
            , 'prop_Text_CreateSerialise
831
            ]
832

    
833
-- ** Node tests
834

    
835
prop_Node_setAlias node name =
836
  Node.name newnode == Node.name node &&
837
  Node.alias newnode == name
838
    where _types = (node::Node.Node, name::String)
839
          newnode = Node.setAlias node name
840

    
841
prop_Node_setOffline node status =
842
  Node.offline newnode ==? status
843
    where newnode = Node.setOffline node status
844

    
845
prop_Node_setXmem node xm =
846
  Node.xMem newnode ==? xm
847
    where newnode = Node.setXmem node xm
848

    
849
prop_Node_setMcpu node mc =
850
  Node.mCpu newnode ==? mc
851
    where newnode = Node.setMcpu node mc
852

    
853
-- | Check that an instance add with too high memory or disk will be
854
-- rejected.
855
prop_Node_addPriFM node inst =
856
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
857
  not (Instance.instanceOffline inst) ==>
858
  case Node.addPri node inst'' of
859
    Types.OpFail Types.FailMem -> True
860
    _ -> False
861
  where _types = (node::Node.Node, inst::Instance.Instance)
862
        inst' = setInstanceSmallerThanNode node inst
863
        inst'' = inst' { Instance.mem = Instance.mem inst }
864

    
865
prop_Node_addPriFD node inst =
866
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
867
    case Node.addPri node inst'' of
868
      Types.OpFail Types.FailDisk -> True
869
      _ -> False
870
    where _types = (node::Node.Node, inst::Instance.Instance)
871
          inst' = setInstanceSmallerThanNode node inst
872
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
873

    
874
prop_Node_addPriFC node inst (Positive extra) =
875
  not (Node.failN1 node) && not (Instance.instanceOffline inst) ==>
876
      case Node.addPri node inst'' of
877
        Types.OpFail Types.FailCPU -> True
878
        _ -> False
879
    where _types = (node::Node.Node, inst::Instance.Instance)
880
          inst' = setInstanceSmallerThanNode node inst
881
          inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
882

    
883
-- | Check that an instance add with too high memory or disk will be
884
-- rejected.
885
prop_Node_addSec node inst pdx =
886
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
887
    not (Instance.instanceOffline inst)) ||
888
   Instance.dsk inst >= Node.fDsk node) &&
889
  not (Node.failN1 node) ==>
890
      isFailure (Node.addSec node inst pdx)
891
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
892

    
893
-- | Check that an offline instance with reasonable disk size can always
894
-- be added.
895
prop_Node_addPriOffline =
896
  forAll (arbitrary `suchThat` ((> 0) . Node.fMem)) $ \node ->
897
  forAll (arbitrary `suchThat`
898
          (\ x ->  (Instance.dsk x  < Node.fDsk node) &&
899
                   Instance.instanceOffline x)) $ \inst ->
900
  case Node.addPri node inst of
901
    Types.OpGood _ -> True
902
    _ -> False
903

    
904
prop_Node_addSecOffline pdx =
905
  forAll (arbitrary `suchThat` ((> 0) . Node.fMem)) $ \node ->
906
  forAll (arbitrary `suchThat`
907
          (\ x ->  (Instance.dsk x  < Node.fDsk node) &&
908
                   Instance.instanceOffline x)) $ \inst ->
909
  case Node.addSec node inst pdx of
910
    Types.OpGood _ -> True
911
    _ -> False
912

    
913
-- | Checks for memory reservation changes.
914
prop_Node_rMem inst =
915
  not (Instance.instanceOffline inst) ==>
916
  forAll (arbitrary `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
917
  -- ab = auto_balance, nb = non-auto_balance
918
  -- we use -1 as the primary node of the instance
919
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True }
920
      inst_ab = setInstanceSmallerThanNode node inst'
921
      inst_nb = inst_ab { Instance.autoBalance = False }
922
      -- now we have the two instances, identical except the
923
      -- autoBalance attribute
924
      orig_rmem = Node.rMem node
925
      inst_idx = Instance.idx inst_ab
926
      node_add_ab = Node.addSec node inst_ab (-1)
927
      node_add_nb = Node.addSec node inst_nb (-1)
928
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
929
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
930
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
931
       (Types.OpGood a_ab, Types.OpGood a_nb,
932
        Types.OpGood d_ab, Types.OpGood d_nb) ->
933
         printTestCase "Consistency checks failed" $
934
           Node.rMem a_ab >  orig_rmem &&
935
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
936
           Node.rMem a_nb == orig_rmem &&
937
           Node.rMem d_ab == orig_rmem &&
938
           Node.rMem d_nb == orig_rmem &&
939
           -- this is not related to rMem, but as good a place to
940
           -- test as any
941
           inst_idx `elem` Node.sList a_ab &&
942
           inst_idx `notElem` Node.sList d_ab
943
       x -> printTestCase ("Failed to add/remove instances: " ++ show x) False
944

    
945
-- | Check mdsk setting.
946
prop_Node_setMdsk node mx =
947
  Node.loDsk node' >= 0 &&
948
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
949
  Node.availDisk node' >= 0 &&
950
  Node.availDisk node' <= Node.fDsk node' &&
951
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
952
  Node.mDsk node' == mx'
953
    where _types = (node::Node.Node, mx::SmallRatio)
954
          node' = Node.setMdsk node mx'
955
          SmallRatio mx' = mx
956

    
957
-- Check tag maps
958
prop_Node_tagMaps_idempotent tags =
959
  Node.delTags (Node.addTags m tags) tags ==? m
960
    where m = Data.Map.empty
961

    
962
prop_Node_tagMaps_reject tags =
963
  not (null tags) ==>
964
  all (\t -> Node.rejectAddTags m [t]) tags
965
    where m = Node.addTags Data.Map.empty tags
966

    
967
prop_Node_showField node =
968
  forAll (elements Node.defaultFields) $ \ field ->
969
  fst (Node.showHeader field) /= Types.unknownField &&
970
  Node.showField node field /= Types.unknownField
971

    
972
prop_Node_computeGroups nodes =
973
  let ng = Node.computeGroups nodes
974
      onlyuuid = map fst ng
975
  in length nodes == sum (map (length . snd) ng) &&
976
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
977
     length (nub onlyuuid) == length onlyuuid &&
978
     (null nodes || not (null ng))
979

    
980
testSuite "Node"
981
            [ 'prop_Node_setAlias
982
            , 'prop_Node_setOffline
983
            , 'prop_Node_setMcpu
984
            , 'prop_Node_setXmem
985
            , 'prop_Node_addPriFM
986
            , 'prop_Node_addPriFD
987
            , 'prop_Node_addPriFC
988
            , 'prop_Node_addSec
989
            , 'prop_Node_addPriOffline
990
            , 'prop_Node_addSecOffline
991
            , 'prop_Node_rMem
992
            , 'prop_Node_setMdsk
993
            , 'prop_Node_tagMaps_idempotent
994
            , 'prop_Node_tagMaps_reject
995
            , 'prop_Node_showField
996
            , 'prop_Node_computeGroups
997
            ]
998

    
999
-- ** Cluster tests
1000

    
1001
-- | Check that the cluster score is close to zero for a homogeneous
1002
-- cluster.
1003
prop_Score_Zero node =
1004
  forAll (choose (1, 1024)) $ \count ->
1005
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1006
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1007
  let fn = Node.buildPeers node Container.empty
1008
      nlst = replicate count fn
1009
      score = Cluster.compCVNodes nlst
1010
  -- we can't say == 0 here as the floating point errors accumulate;
1011
  -- this should be much lower than the default score in CLI.hs
1012
  in score <= 1e-12
1013

    
1014
-- | Check that cluster stats are sane.
1015
prop_CStats_sane =
1016
  forAll (choose (1, 1024)) $ \count ->
1017
  forAll genOnlineNode $ \node ->
1018
  let fn = Node.buildPeers node Container.empty
1019
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1020
      nl = Container.fromList nlst
1021
      cstats = Cluster.totalResources nl
1022
  in Cluster.csAdsk cstats >= 0 &&
1023
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1024

    
1025
-- | Check that one instance is allocated correctly, without
1026
-- rebalances needed.
1027
prop_ClusterAlloc_sane inst =
1028
  forAll (choose (5, 20)) $ \count ->
1029
  forAll genOnlineNode $ \node ->
1030
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1031
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
1032
     Cluster.tryAlloc nl il inst' of
1033
       Types.Bad _ -> False
1034
       Types.Ok as ->
1035
         case Cluster.asSolution as of
1036
           Nothing -> False
1037
           Just (xnl, xi, _, cv) ->
1038
             let il' = Container.add (Instance.idx xi) xi il
1039
                 tbl = Cluster.Table xnl il' cv []
1040
             in not (canBalance tbl True True False)
1041

    
1042
-- | Checks that on a 2-5 node cluster, we can allocate a random
1043
-- instance spec via tiered allocation (whatever the original instance
1044
-- spec), on either one or two nodes.
1045
prop_ClusterCanTieredAlloc inst =
1046
  forAll (choose (2, 5)) $ \count ->
1047
  forAll (choose (1, 2)) $ \rqnodes ->
1048
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1049
  let nl = makeSmallCluster node count
1050
      il = Container.empty
1051
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1052
  in case allocnodes >>= \allocnodes' ->
1053
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1054
       Types.Bad _ -> False
1055
       Types.Ok (_, _, il', ixes, cstats) -> not (null ixes) &&
1056
                                             IntMap.size il' == length ixes &&
1057
                                             length ixes == length cstats
1058

    
1059
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1060
-- we can also evacuate it.
1061
prop_ClusterAllocEvac inst =
1062
  forAll (choose (4, 8)) $ \count ->
1063
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1064
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1065
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
1066
     Cluster.tryAlloc nl il inst' of
1067
       Types.Bad _ -> False
1068
       Types.Ok as ->
1069
         case Cluster.asSolution as of
1070
           Nothing -> False
1071
           Just (xnl, xi, _, _) ->
1072
             let sdx = Instance.sNode xi
1073
                 il' = Container.add (Instance.idx xi) xi il
1074
             in case IAlloc.processRelocate defGroupList xnl il'
1075
                  (Instance.idx xi) 1 [sdx] of
1076
                  Types.Ok _ -> True
1077
                  _ -> False
1078

    
1079
-- | Check that allocating multiple instances on a cluster, then
1080
-- adding an empty node, results in a valid rebalance.
1081
prop_ClusterAllocBalance =
1082
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1083
  forAll (choose (3, 5)) $ \count ->
1084
  not (Node.offline node) && not (Node.failN1 node) ==>
1085
  let nl = makeSmallCluster node count
1086
      (hnode, nl') = IntMap.deleteFindMax nl
1087
      il = Container.empty
1088
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1089
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1090
  in case allocnodes >>= \allocnodes' ->
1091
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1092
       Types.Bad _ -> printTestCase "Failed to allocate" False
1093
       Types.Ok (_, _, _, [], _) -> printTestCase "Failed to allocate" False
1094
       Types.Ok (_, xnl, il', _, _) ->
1095
         let ynl = Container.add (Node.idx hnode) hnode xnl
1096
             cv = Cluster.compCV ynl
1097
             tbl = Cluster.Table ynl il' cv []
1098
         in printTestCase "Failed to rebalance" $
1099
            canBalance tbl True True False
1100

    
1101
-- | Checks consistency.
1102
prop_ClusterCheckConsistency node inst =
1103
  let nl = makeSmallCluster node 3
1104
      [node1, node2, node3] = Container.elems nl
1105
      node3' = node3 { Node.group = 1 }
1106
      nl' = Container.add (Node.idx node3') node3' nl
1107
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1108
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1109
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1110
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1111
  in null (ccheck [(0, inst1)]) &&
1112
     null (ccheck [(0, inst2)]) &&
1113
     (not . null $ ccheck [(0, inst3)])
1114

    
1115
-- | For now, we only test that we don't lose instances during the split.
1116
prop_ClusterSplitCluster node inst =
1117
  forAll (choose (0, 100)) $ \icnt ->
1118
  let nl = makeSmallCluster node 2
1119
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1120
                   (nl, Container.empty) [1..icnt]
1121
      gni = Cluster.splitCluster nl' il'
1122
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1123
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1124
                                 (Container.elems nl'')) gni
1125

    
1126
-- | Helper function to check if we can allocate an instance on a
1127
-- given node list.
1128
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1129
canAllocOn nl reqnodes inst =
1130
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1131
       Cluster.tryAlloc nl (Container.empty) inst of
1132
       Types.Bad _ -> False
1133
       Types.Ok as ->
1134
         case Cluster.asSolution as of
1135
           Nothing -> False
1136
           Just _ -> True
1137

    
1138
-- | Checks that allocation obeys minimum and maximum instance
1139
-- policies. The unittest generates a random node, duplicates it count
1140
-- times, and generates a random instance that can be allocated on
1141
-- this mini-cluster; it then checks that after applying a policy that
1142
-- the instance doesn't fits, the allocation fails.
1143
prop_ClusterAllocPolicy node =
1144
  -- rqn is the required nodes (1 or 2)
1145
  forAll (choose (1, 2)) $ \rqn ->
1146
  forAll (choose (5, 20)) $ \count ->
1147
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1148
         $ \inst ->
1149
  forAll (arbitrary `suchThat` (isFailure .
1150
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1151
  let node' = Node.setPolicy ipol node
1152
      nl = makeSmallCluster node' count
1153
  in not $ canAllocOn nl rqn inst
1154

    
1155
testSuite "Cluster"
1156
            [ 'prop_Score_Zero
1157
            , 'prop_CStats_sane
1158
            , 'prop_ClusterAlloc_sane
1159
            , 'prop_ClusterCanTieredAlloc
1160
            , 'prop_ClusterAllocEvac
1161
            , 'prop_ClusterAllocBalance
1162
            , 'prop_ClusterCheckConsistency
1163
            , 'prop_ClusterSplitCluster
1164
            , 'prop_ClusterAllocPolicy
1165
            ]
1166

    
1167
-- ** OpCodes tests
1168

    
1169
-- | Check that opcode serialization is idempotent.
1170
prop_OpCodes_serialization op =
1171
  case J.readJSON (J.showJSON op) of
1172
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1173
    J.Ok op' -> op ==? op'
1174
  where _types = op::OpCodes.OpCode
1175

    
1176
testSuite "OpCodes"
1177
            [ 'prop_OpCodes_serialization ]
1178

    
1179
-- ** Jobs tests
1180

    
1181
-- | Check that (queued) job\/opcode status serialization is idempotent.
1182
prop_OpStatus_serialization os =
1183
  case J.readJSON (J.showJSON os) of
1184
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1185
    J.Ok os' -> os ==? os'
1186
  where _types = os::Jobs.OpStatus
1187

    
1188
prop_JobStatus_serialization js =
1189
  case J.readJSON (J.showJSON js) of
1190
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1191
    J.Ok js' -> js ==? js'
1192
  where _types = js::Jobs.JobStatus
1193

    
1194
testSuite "Jobs"
1195
            [ 'prop_OpStatus_serialization
1196
            , 'prop_JobStatus_serialization
1197
            ]
1198

    
1199
-- ** Loader tests
1200

    
1201
prop_Loader_lookupNode ktn inst node =
1202
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1203
    where nl = Data.Map.fromList ktn
1204

    
1205
prop_Loader_lookupInstance kti inst =
1206
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1207
    where il = Data.Map.fromList kti
1208

    
1209
prop_Loader_assignIndices nodes =
1210
  Data.Map.size nassoc == length nodes &&
1211
  Container.size kt == length nodes &&
1212
  (if not (null nodes)
1213
   then maximum (IntMap.keys kt) == length nodes - 1
1214
   else True)
1215
    where (nassoc, kt) =
1216
            Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1217

    
1218
-- | Checks that the number of primary instances recorded on the nodes
1219
-- is zero.
1220
prop_Loader_mergeData ns =
1221
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1222
  in case Loader.mergeData [] [] [] []
1223
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1224
    Types.Bad _ -> False
1225
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1226
      let nodes = Container.elems nl
1227
          instances = Container.elems il
1228
      in (sum . map (length . Node.pList)) nodes == 0 &&
1229
         null instances
1230

    
1231
-- | Check that compareNameComponent on equal strings works.
1232
prop_Loader_compareNameComponent_equal :: String -> Bool
1233
prop_Loader_compareNameComponent_equal s =
1234
  Loader.compareNameComponent s s ==
1235
    Loader.LookupResult Loader.ExactMatch s
1236

    
1237
-- | Check that compareNameComponent on prefix strings works.
1238
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1239
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1240
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1241
    Loader.LookupResult Loader.PartialMatch s1
1242

    
1243
testSuite "Loader"
1244
            [ 'prop_Loader_lookupNode
1245
            , 'prop_Loader_lookupInstance
1246
            , 'prop_Loader_assignIndices
1247
            , 'prop_Loader_mergeData
1248
            , 'prop_Loader_compareNameComponent_equal
1249
            , 'prop_Loader_compareNameComponent_prefix
1250
            ]
1251

    
1252
-- ** Types tests
1253

    
1254
prop_Types_AllocPolicy_serialisation apol =
1255
  case J.readJSON (J.showJSON apol) of
1256
    J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1257
              p == apol
1258
    J.Error s -> printTestCase ("failed to deserialise: " ++ s) False
1259
      where _types = apol::Types.AllocPolicy
1260

    
1261
prop_Types_DiskTemplate_serialisation dt =
1262
  case J.readJSON (J.showJSON dt) of
1263
    J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1264
              p == dt
1265
    J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1266
                 False
1267
      where _types = dt::Types.DiskTemplate
1268

    
1269
prop_Types_opToResult op =
1270
  case op of
1271
    Types.OpFail _ -> Types.isBad r
1272
    Types.OpGood v -> case r of
1273
                        Types.Bad _ -> False
1274
                        Types.Ok v' -> v == v'
1275
  where r = Types.opToResult op
1276
        _types = op::Types.OpResult Int
1277

    
1278
prop_Types_eitherToResult ei =
1279
  case ei of
1280
    Left _ -> Types.isBad r
1281
    Right v -> case r of
1282
                 Types.Bad _ -> False
1283
                 Types.Ok v' -> v == v'
1284
    where r = Types.eitherToResult ei
1285
          _types = ei::Either String Int
1286

    
1287
testSuite "Types"
1288
            [ 'prop_Types_AllocPolicy_serialisation
1289
            , 'prop_Types_DiskTemplate_serialisation
1290
            , 'prop_Types_opToResult
1291
            , 'prop_Types_eitherToResult
1292
            ]