Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (48.3 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 Types.EvacMode where
371
  arbitrary = elements [minBound..maxBound]
372

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

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

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

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

    
414
-- * Actual tests
415

    
416
-- ** Utils tests
417

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

    
425
-- | Split and join should always be idempotent.
426
prop_Utils_commaSplitJoin s =
427
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
428

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

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

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

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

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

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

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

    
499
-- ** PeerMap tests
500

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

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

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

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

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

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

    
545
-- ** Container tests
546

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

    
557
prop_Container_nameOf node =
558
  let nl = makeSmallCluster node 1
559
      fnode = head (Container.elems nl)
560
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
561

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

    
584
testSuite "Container"
585
            [ 'prop_Container_addTwo
586
            , 'prop_Container_nameOf
587
            , 'prop_Container_findByName
588
            ]
589

    
590
-- ** Instance tests
591

    
592
-- Simple instance tests, we only have setter/getters
593

    
594
prop_Instance_creat inst =
595
  Instance.name inst ==? Instance.alias inst
596

    
597
prop_Instance_setIdx inst idx =
598
  Instance.idx (Instance.setIdx inst idx) ==? idx
599
    where _types = (inst::Instance.Instance, idx::Types.Idx)
600

    
601
prop_Instance_setName inst name =
602
  Instance.name newinst == name &&
603
  Instance.alias newinst == name
604
    where _types = (inst::Instance.Instance, name::String)
605
          newinst = Instance.setName inst name
606

    
607
prop_Instance_setAlias inst name =
608
  Instance.name newinst == Instance.name inst &&
609
  Instance.alias newinst == name
610
    where _types = (inst::Instance.Instance, name::String)
611
          newinst = Instance.setAlias inst name
612

    
613
prop_Instance_setPri inst pdx =
614
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
615
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
616

    
617
prop_Instance_setSec inst sdx =
618
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
619
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
620

    
621
prop_Instance_setBoth inst pdx sdx =
622
  Instance.pNode si == pdx && Instance.sNode si == sdx
623
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
624
          si = Instance.setBoth inst pdx sdx
625

    
626
prop_Instance_shrinkMG inst =
627
  Instance.mem inst >= 2 * Types.unitMem ==>
628
    case Instance.shrinkByType inst Types.FailMem of
629
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
630
      _ -> False
631

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

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

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

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

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

    
661
prop_Instance_setMovable inst m =
662
  Instance.movable inst' ==? m
663
    where inst' = Instance.setMovable inst m
664

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

    
682
-- ** Text backend tests
683

    
684
-- Instance text loader tests
685

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

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

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

    
765
prop_Text_Load_NodeFail fields =
766
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
767

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

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

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

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

    
825
testSuite "Text"
826
            [ 'prop_Text_Load_Instance
827
            , 'prop_Text_Load_InstanceFail
828
            , 'prop_Text_Load_Node
829
            , 'prop_Text_Load_NodeFail
830
            , 'prop_Text_NodeLSIdempotent
831
            , 'prop_Text_ISpecIdempotent
832
            , 'prop_Text_IPolicyIdempotent
833
            , 'prop_Text_CreateSerialise
834
            ]
835

    
836
-- ** Node tests
837

    
838
prop_Node_setAlias node name =
839
  Node.name newnode == Node.name node &&
840
  Node.alias newnode == name
841
    where _types = (node::Node.Node, name::String)
842
          newnode = Node.setAlias node name
843

    
844
prop_Node_setOffline node status =
845
  Node.offline newnode ==? status
846
    where newnode = Node.setOffline node status
847

    
848
prop_Node_setXmem node xm =
849
  Node.xMem newnode ==? xm
850
    where newnode = Node.setXmem node xm
851

    
852
prop_Node_setMcpu node mc =
853
  Node.mCpu newnode ==? mc
854
    where newnode = Node.setMcpu node mc
855

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

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

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

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

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

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

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

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

    
960
-- Check tag maps
961
prop_Node_tagMaps_idempotent tags =
962
  Node.delTags (Node.addTags m tags) tags ==? m
963
    where m = Data.Map.empty
964

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

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

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

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

    
1002
-- ** Cluster tests
1003

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

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

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

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

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

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

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

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

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

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

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

    
1170
-- ** OpCodes tests
1171

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

    
1179
testSuite "OpCodes"
1180
            [ 'prop_OpCodes_serialization ]
1181

    
1182
-- ** Jobs tests
1183

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

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

    
1197
testSuite "Jobs"
1198
            [ 'prop_OpStatus_serialization
1199
            , 'prop_JobStatus_serialization
1200
            ]
1201

    
1202
-- ** Loader tests
1203

    
1204
prop_Loader_lookupNode ktn inst node =
1205
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1206
    where nl = Data.Map.fromList ktn
1207

    
1208
prop_Loader_lookupInstance kti inst =
1209
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1210
    where il = Data.Map.fromList kti
1211

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

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

    
1234
-- | Check that compareNameComponent on equal strings works.
1235
prop_Loader_compareNameComponent_equal :: String -> Bool
1236
prop_Loader_compareNameComponent_equal s =
1237
  Loader.compareNameComponent s s ==
1238
    Loader.LookupResult Loader.ExactMatch s
1239

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

    
1246
testSuite "Loader"
1247
            [ 'prop_Loader_lookupNode
1248
            , 'prop_Loader_lookupInstance
1249
            , 'prop_Loader_assignIndices
1250
            , 'prop_Loader_mergeData
1251
            , 'prop_Loader_compareNameComponent_equal
1252
            , 'prop_Loader_compareNameComponent_prefix
1253
            ]
1254

    
1255
-- ** Types tests
1256

    
1257
prop_Types_AllocPolicy_serialisation apol =
1258
  case J.readJSON (J.showJSON apol) of
1259
    J.Ok p -> p ==? apol
1260
    J.Error s -> printTestCase ("failed to deserialise: " ++ s) False
1261
      where _types = apol::Types.AllocPolicy
1262

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

    
1270
prop_Types_ISpec_serialisation ispec =
1271
  case J.readJSON (J.showJSON ispec) of
1272
    J.Ok p -> p ==? ispec
1273
    J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1274
                 False
1275
      where _types = ispec::Types.ISpec
1276

    
1277
prop_Types_IPolicy_serialisation ipol =
1278
  case J.readJSON (J.showJSON ipol) of
1279
    J.Ok p -> p ==? ipol
1280
    J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1281
                 False
1282
      where _types = ipol::Types.IPolicy
1283

    
1284
prop_Types_EvacMode_serialisation em =
1285
  case J.readJSON (J.showJSON em) of
1286
    J.Ok p -> p ==? em
1287
    J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1288
                 False
1289
      where _types = em::Types.EvacMode
1290

    
1291
prop_Types_opToResult op =
1292
  case op of
1293
    Types.OpFail _ -> Types.isBad r
1294
    Types.OpGood v -> case r of
1295
                        Types.Bad _ -> False
1296
                        Types.Ok v' -> v == v'
1297
  where r = Types.opToResult op
1298
        _types = op::Types.OpResult Int
1299

    
1300
prop_Types_eitherToResult ei =
1301
  case ei of
1302
    Left _ -> Types.isBad r
1303
    Right v -> case r of
1304
                 Types.Bad _ -> False
1305
                 Types.Ok v' -> v == v'
1306
    where r = Types.eitherToResult ei
1307
          _types = ei::Either String Int
1308

    
1309
testSuite "Types"
1310
            [ 'prop_Types_AllocPolicy_serialisation
1311
            , 'prop_Types_DiskTemplate_serialisation
1312
            , 'prop_Types_ISpec_serialisation
1313
            , 'prop_Types_IPolicy_serialisation
1314
            , 'prop_Types_EvacMode_serialisation
1315
            , 'prop_Types_opToResult
1316
            , 'prop_Types_eitherToResult
1317
            ]