Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 6a855aaa

History | View | Annotate | Download (51.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
-- | Show a message and fail the test.
143
failTest :: String -> Property
144
failTest msg = printTestCase msg False
145

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

    
153
-- | Check if an instance is smaller than a node.
154
isInstanceSmallerThanNode node inst =
155
  Instance.mem inst   <= Node.availMem node `div` 2 &&
156
  Instance.dsk inst   <= Node.availDisk node `div` 2 &&
157
  Instance.vcpus inst <= Node.availCpu node `div` 2
158

    
159
-- | Create an instance given its spec.
160
createInstance mem dsk vcpus =
161
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
162
    Types.DTDrbd8
163

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

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

    
184
-- | Checks if a node is "big" enough.
185
isNodeBig :: Int -> Node.Node -> Bool
186
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
187
                      && Node.availMem node > size * Types.unitMem
188
                      && Node.availCpu node > size * Types.unitCpu
189

    
190
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
191
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
192

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

    
212
-- * Arbitrary instances
213

    
214
-- | Defines a DNS name.
215
newtype DNSChar = DNSChar { dnsGetChar::Char }
216

    
217
instance Arbitrary DNSChar where
218
  arbitrary = do
219
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
220
    return (DNSChar x)
221

    
222
getName :: Gen String
223
getName = do
224
  n <- choose (1, 64)
225
  dn <- vector n::Gen [DNSChar]
226
  return (map dnsGetChar dn)
227

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

    
236
-- | Defines a tag type.
237
newtype TagChar = TagChar { tagGetChar :: Char }
238

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

    
244
instance Arbitrary TagChar where
245
  arbitrary = do
246
    c <- elements tagChar
247
    return (TagChar c)
248

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

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

    
268
instance Arbitrary Types.InstanceStatus where
269
    arbitrary = elements [minBound..maxBound]
270

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

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

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

    
324
-- and a random node
325
instance Arbitrary Node.Node where
326
  arbitrary = genNode Nothing Nothing
327

    
328
-- replace disks
329
instance Arbitrary OpCodes.ReplaceDisksMode where
330
  arbitrary = elements [minBound..maxBound]
331

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

    
353
instance Arbitrary Jobs.OpStatus where
354
  arbitrary = elements [minBound..maxBound]
355

    
356
instance Arbitrary Jobs.JobStatus where
357
  arbitrary = elements [minBound..maxBound]
358

    
359
newtype SmallRatio = SmallRatio Double deriving Show
360
instance Arbitrary SmallRatio where
361
  arbitrary = do
362
    v <- choose (0, 1)
363
    return $ SmallRatio v
364

    
365
instance Arbitrary Types.AllocPolicy where
366
  arbitrary = elements [minBound..maxBound]
367

    
368
instance Arbitrary Types.DiskTemplate where
369
  arbitrary = elements [minBound..maxBound]
370

    
371
instance Arbitrary Types.FailMode where
372
  arbitrary = elements [minBound..maxBound]
373

    
374
instance Arbitrary Types.EvacMode where
375
  arbitrary = elements [minBound..maxBound]
376

    
377
instance Arbitrary a => Arbitrary (Types.OpResult a) where
378
  arbitrary = arbitrary >>= \c ->
379
              if c
380
                then liftM Types.OpGood arbitrary
381
                else liftM Types.OpFail arbitrary
382

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

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

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

    
418
-- * Actual tests
419

    
420
-- ** Utils tests
421

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

    
429
-- | Split and join should always be idempotent.
430
prop_Utils_commaSplitJoin s =
431
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
432

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

    
443
-- | Test that functional if' behaves like the syntactic sugar if.
444
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
445
prop_Utils_if'if cnd a b =
446
  Utils.if' cnd a b ==? if cnd then a else b
447

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

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

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

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

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

    
503
-- ** PeerMap tests
504

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

    
513
-- | Make sure remove is idempotent.
514
prop_PeerMap_removeIdempotent pmap key =
515
  fn puniq ==? fn (fn puniq)
516
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
517
          fn = PeerMap.remove key
518
          puniq = PeerMap.accumArray const pmap
519

    
520
-- | Make sure a missing item returns 0.
521
prop_PeerMap_findMissing pmap key =
522
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
523
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
524
          puniq = PeerMap.accumArray const pmap
525

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

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

    
540
-- | List of tests for the PeerMap module.
541
testSuite "PeerMap"
542
            [ 'prop_PeerMap_addIdempotent
543
            , 'prop_PeerMap_removeIdempotent
544
            , 'prop_PeerMap_maxElem
545
            , 'prop_PeerMap_addFind
546
            , 'prop_PeerMap_findMissing
547
            ]
548

    
549
-- ** Container tests
550

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

    
561
prop_Container_nameOf node =
562
  let nl = makeSmallCluster node 1
563
      fnode = head (Container.elems nl)
564
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
565

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

    
588
testSuite "Container"
589
            [ 'prop_Container_addTwo
590
            , 'prop_Container_nameOf
591
            , 'prop_Container_findByName
592
            ]
593

    
594
-- ** Instance tests
595

    
596
-- Simple instance tests, we only have setter/getters
597

    
598
prop_Instance_creat inst =
599
  Instance.name inst ==? Instance.alias inst
600

    
601
prop_Instance_setIdx inst idx =
602
  Instance.idx (Instance.setIdx inst idx) ==? idx
603
    where _types = (inst::Instance.Instance, idx::Types.Idx)
604

    
605
prop_Instance_setName inst name =
606
  Instance.name newinst == name &&
607
  Instance.alias newinst == name
608
    where _types = (inst::Instance.Instance, name::String)
609
          newinst = Instance.setName inst name
610

    
611
prop_Instance_setAlias inst name =
612
  Instance.name newinst == Instance.name inst &&
613
  Instance.alias newinst == name
614
    where _types = (inst::Instance.Instance, name::String)
615
          newinst = Instance.setAlias inst name
616

    
617
prop_Instance_setPri inst pdx =
618
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
619
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
620

    
621
prop_Instance_setSec inst sdx =
622
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
623
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
624

    
625
prop_Instance_setBoth inst pdx sdx =
626
  Instance.pNode si == pdx && Instance.sNode si == sdx
627
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
628
          si = Instance.setBoth inst pdx sdx
629

    
630
prop_Instance_shrinkMG inst =
631
  Instance.mem inst >= 2 * Types.unitMem ==>
632
    case Instance.shrinkByType inst Types.FailMem of
633
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
634
      _ -> False
635

    
636
prop_Instance_shrinkMF inst =
637
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
638
    let inst' = inst { Instance.mem = mem}
639
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
640

    
641
prop_Instance_shrinkCG inst =
642
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
643
    case Instance.shrinkByType inst Types.FailCPU of
644
      Types.Ok inst' ->
645
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
646
      _ -> False
647

    
648
prop_Instance_shrinkCF inst =
649
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
650
    let inst' = inst { Instance.vcpus = vcpus }
651
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
652

    
653
prop_Instance_shrinkDG inst =
654
  Instance.dsk inst >= 2 * Types.unitDsk ==>
655
    case Instance.shrinkByType inst Types.FailDisk of
656
      Types.Ok inst' ->
657
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
658
      _ -> False
659

    
660
prop_Instance_shrinkDF inst =
661
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
662
    let inst' = inst { Instance.dsk = dsk }
663
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
664

    
665
prop_Instance_setMovable inst m =
666
  Instance.movable inst' ==? m
667
    where inst' = Instance.setMovable inst m
668

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

    
686
-- ** Text backend tests
687

    
688
-- Instance text loader tests
689

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

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

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

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

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

    
778
prop_Text_ISpecIdempotent ispec =
779
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
780
       Text.serializeISpec $ ispec of
781
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
782
    Types.Ok ispec' -> ispec ==? ispec'
783

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

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

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

    
837
-- ** Node tests
838

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1003
-- ** Cluster tests
1004

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

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

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

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

    
1063
-- | Helper function to create a cluster with the given range of nodes
1064
-- and allocate an instance on it.
1065
genClusterAlloc count node inst =
1066
  let nl = makeSmallCluster node count
1067
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
1068
     Cluster.tryAlloc nl Container.empty inst of
1069
       Types.Bad _ -> Types.Bad "Can't allocate"
1070
       Types.Ok as ->
1071
         case Cluster.asSolution as of
1072
           Nothing -> Types.Bad "Empty solution?"
1073
           Just (xnl, xi, _, _) ->
1074
             let xil = Container.add (Instance.idx xi) xi Container.empty
1075
             in Types.Ok (xnl, xil, xi)
1076

    
1077
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1078
-- we can also relocate it.
1079
prop_ClusterAllocRelocate =
1080
  forAll (choose (4, 8)) $ \count ->
1081
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1082
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1083
  case genClusterAlloc count node inst of
1084
    Types.Bad msg -> failTest msg
1085
    Types.Ok (nl, il, inst') ->
1086
      case IAlloc.processRelocate defGroupList nl il
1087
             (Instance.idx inst) 1 [Instance.sNode inst'] of
1088
        Types.Ok _ -> printTestCase "??" True  -- huh, how to make
1089
                                               -- this nicer...
1090
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1091

    
1092
-- | Helper property checker for the result of a nodeEvac or
1093
-- changeGroup operation.
1094
check_EvacMode grp inst result =
1095
  case result of
1096
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1097
    Types.Ok (_, _, es) ->
1098
      let moved = Cluster.esMoved es
1099
          failed = Cluster.esFailed es
1100
          opcodes = not . null $ Cluster.esOpCodes es
1101
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1102
         failmsg "'opcodes' is null" opcodes .&&.
1103
         case moved of
1104
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1105
                               .&&.
1106
                               failmsg "wrong target group"
1107
                                         (gdx == Group.idx grp)
1108
           v -> failmsg  ("invalid solution: " ++ show v) False
1109
  where failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1110
        idx = Instance.idx inst
1111

    
1112
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1113
-- we can also node-evacuate it.
1114
prop_ClusterAllocEvacuate =
1115
  forAll (choose (4, 8)) $ \count ->
1116
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1117
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1118
  case genClusterAlloc count node inst of
1119
    Types.Bad msg -> failTest msg
1120
    Types.Ok (nl, il, inst') ->
1121
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1122
                              Cluster.tryNodeEvac defGroupList nl il mode
1123
                                [Instance.idx inst']) [minBound..maxBound]
1124

    
1125
-- | Checks that on a 4-8 node cluster with two node groups, once we
1126
-- allocate an instance on the first node group, we can also change
1127
-- its group.
1128
prop_ClusterAllocChangeGroup =
1129
  forAll (choose (4, 8)) $ \count ->
1130
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1131
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1132
  case genClusterAlloc count node inst of
1133
    Types.Bad msg -> failTest msg
1134
    Types.Ok (nl, il, inst') ->
1135
      -- we need to add a second node group and nodes to the cluster
1136
      let nl2 = Container.elems $ makeSmallCluster node count
1137
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1138
          maxndx = maximum . map Node.idx $ nl2
1139
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1140
                             , Node.idx = Node.idx n + maxndx }) nl2
1141
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1142
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1143
          nl' = IntMap.union nl nl4
1144
      in check_EvacMode grp2 inst' $
1145
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1146

    
1147
-- | Check that allocating multiple instances on a cluster, then
1148
-- adding an empty node, results in a valid rebalance.
1149
prop_ClusterAllocBalance =
1150
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1151
  forAll (choose (3, 5)) $ \count ->
1152
  not (Node.offline node) && not (Node.failN1 node) ==>
1153
  let nl = makeSmallCluster node count
1154
      (hnode, nl') = IntMap.deleteFindMax nl
1155
      il = Container.empty
1156
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1157
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1158
  in case allocnodes >>= \allocnodes' ->
1159
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1160
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1161
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1162
       Types.Ok (_, xnl, il', _, _) ->
1163
         let ynl = Container.add (Node.idx hnode) hnode xnl
1164
             cv = Cluster.compCV ynl
1165
             tbl = Cluster.Table ynl il' cv []
1166
         in printTestCase "Failed to rebalance" $
1167
            canBalance tbl True True False
1168

    
1169
-- | Checks consistency.
1170
prop_ClusterCheckConsistency node inst =
1171
  let nl = makeSmallCluster node 3
1172
      [node1, node2, node3] = Container.elems nl
1173
      node3' = node3 { Node.group = 1 }
1174
      nl' = Container.add (Node.idx node3') node3' nl
1175
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1176
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1177
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1178
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1179
  in null (ccheck [(0, inst1)]) &&
1180
     null (ccheck [(0, inst2)]) &&
1181
     (not . null $ ccheck [(0, inst3)])
1182

    
1183
-- | For now, we only test that we don't lose instances during the split.
1184
prop_ClusterSplitCluster node inst =
1185
  forAll (choose (0, 100)) $ \icnt ->
1186
  let nl = makeSmallCluster node 2
1187
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1188
                   (nl, Container.empty) [1..icnt]
1189
      gni = Cluster.splitCluster nl' il'
1190
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1191
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1192
                                 (Container.elems nl'')) gni
1193

    
1194
-- | Helper function to check if we can allocate an instance on a
1195
-- given node list.
1196
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1197
canAllocOn nl reqnodes inst =
1198
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1199
       Cluster.tryAlloc nl (Container.empty) inst of
1200
       Types.Bad _ -> False
1201
       Types.Ok as ->
1202
         case Cluster.asSolution as of
1203
           Nothing -> False
1204
           Just _ -> True
1205

    
1206
-- | Checks that allocation obeys minimum and maximum instance
1207
-- policies. The unittest generates a random node, duplicates it count
1208
-- times, and generates a random instance that can be allocated on
1209
-- this mini-cluster; it then checks that after applying a policy that
1210
-- the instance doesn't fits, the allocation fails.
1211
prop_ClusterAllocPolicy node =
1212
  -- rqn is the required nodes (1 or 2)
1213
  forAll (choose (1, 2)) $ \rqn ->
1214
  forAll (choose (5, 20)) $ \count ->
1215
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1216
         $ \inst ->
1217
  forAll (arbitrary `suchThat` (isFailure .
1218
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1219
  let node' = Node.setPolicy ipol node
1220
      nl = makeSmallCluster node' count
1221
  in not $ canAllocOn nl rqn inst
1222

    
1223
testSuite "Cluster"
1224
            [ 'prop_Score_Zero
1225
            , 'prop_CStats_sane
1226
            , 'prop_ClusterAlloc_sane
1227
            , 'prop_ClusterCanTieredAlloc
1228
            , 'prop_ClusterAllocRelocate
1229
            , 'prop_ClusterAllocEvacuate
1230
            , 'prop_ClusterAllocChangeGroup
1231
            , 'prop_ClusterAllocBalance
1232
            , 'prop_ClusterCheckConsistency
1233
            , 'prop_ClusterSplitCluster
1234
            , 'prop_ClusterAllocPolicy
1235
            ]
1236

    
1237
-- ** OpCodes tests
1238

    
1239
-- | Check that opcode serialization is idempotent.
1240
prop_OpCodes_serialization op =
1241
  case J.readJSON (J.showJSON op) of
1242
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1243
    J.Ok op' -> op ==? op'
1244
  where _types = op::OpCodes.OpCode
1245

    
1246
testSuite "OpCodes"
1247
            [ 'prop_OpCodes_serialization ]
1248

    
1249
-- ** Jobs tests
1250

    
1251
-- | Check that (queued) job\/opcode status serialization is idempotent.
1252
prop_OpStatus_serialization os =
1253
  case J.readJSON (J.showJSON os) of
1254
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1255
    J.Ok os' -> os ==? os'
1256
  where _types = os::Jobs.OpStatus
1257

    
1258
prop_JobStatus_serialization js =
1259
  case J.readJSON (J.showJSON js) of
1260
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1261
    J.Ok js' -> js ==? js'
1262
  where _types = js::Jobs.JobStatus
1263

    
1264
testSuite "Jobs"
1265
            [ 'prop_OpStatus_serialization
1266
            , 'prop_JobStatus_serialization
1267
            ]
1268

    
1269
-- ** Loader tests
1270

    
1271
prop_Loader_lookupNode ktn inst node =
1272
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1273
    where nl = Data.Map.fromList ktn
1274

    
1275
prop_Loader_lookupInstance kti inst =
1276
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1277
    where il = Data.Map.fromList kti
1278

    
1279
prop_Loader_assignIndices nodes =
1280
  Data.Map.size nassoc == length nodes &&
1281
  Container.size kt == length nodes &&
1282
  (if not (null nodes)
1283
   then maximum (IntMap.keys kt) == length nodes - 1
1284
   else True)
1285
    where (nassoc, kt) =
1286
            Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1287

    
1288
-- | Checks that the number of primary instances recorded on the nodes
1289
-- is zero.
1290
prop_Loader_mergeData ns =
1291
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1292
  in case Loader.mergeData [] [] [] []
1293
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1294
    Types.Bad _ -> False
1295
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1296
      let nodes = Container.elems nl
1297
          instances = Container.elems il
1298
      in (sum . map (length . Node.pList)) nodes == 0 &&
1299
         null instances
1300

    
1301
-- | Check that compareNameComponent on equal strings works.
1302
prop_Loader_compareNameComponent_equal :: String -> Bool
1303
prop_Loader_compareNameComponent_equal s =
1304
  Loader.compareNameComponent s s ==
1305
    Loader.LookupResult Loader.ExactMatch s
1306

    
1307
-- | Check that compareNameComponent on prefix strings works.
1308
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1309
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1310
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1311
    Loader.LookupResult Loader.PartialMatch s1
1312

    
1313
testSuite "Loader"
1314
            [ 'prop_Loader_lookupNode
1315
            , 'prop_Loader_lookupInstance
1316
            , 'prop_Loader_assignIndices
1317
            , 'prop_Loader_mergeData
1318
            , 'prop_Loader_compareNameComponent_equal
1319
            , 'prop_Loader_compareNameComponent_prefix
1320
            ]
1321

    
1322
-- ** Types tests
1323

    
1324
prop_Types_AllocPolicy_serialisation apol =
1325
  case J.readJSON (J.showJSON apol) of
1326
    J.Ok p -> p ==? apol
1327
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1328
      where _types = apol::Types.AllocPolicy
1329

    
1330
prop_Types_DiskTemplate_serialisation dt =
1331
  case J.readJSON (J.showJSON dt) of
1332
    J.Ok p -> p ==? dt
1333
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1334
      where _types = dt::Types.DiskTemplate
1335

    
1336
prop_Types_ISpec_serialisation ispec =
1337
  case J.readJSON (J.showJSON ispec) of
1338
    J.Ok p -> p ==? ispec
1339
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1340
      where _types = ispec::Types.ISpec
1341

    
1342
prop_Types_IPolicy_serialisation ipol =
1343
  case J.readJSON (J.showJSON ipol) of
1344
    J.Ok p -> p ==? ipol
1345
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1346
      where _types = ipol::Types.IPolicy
1347

    
1348
prop_Types_EvacMode_serialisation em =
1349
  case J.readJSON (J.showJSON em) of
1350
    J.Ok p -> p ==? em
1351
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1352
      where _types = em::Types.EvacMode
1353

    
1354
prop_Types_opToResult op =
1355
  case op of
1356
    Types.OpFail _ -> Types.isBad r
1357
    Types.OpGood v -> case r of
1358
                        Types.Bad _ -> False
1359
                        Types.Ok v' -> v == v'
1360
  where r = Types.opToResult op
1361
        _types = op::Types.OpResult Int
1362

    
1363
prop_Types_eitherToResult ei =
1364
  case ei of
1365
    Left _ -> Types.isBad r
1366
    Right v -> case r of
1367
                 Types.Bad _ -> False
1368
                 Types.Ok v' -> v == v'
1369
    where r = Types.eitherToResult ei
1370
          _types = ei::Either String Int
1371

    
1372
testSuite "Types"
1373
            [ 'prop_Types_AllocPolicy_serialisation
1374
            , 'prop_Types_DiskTemplate_serialisation
1375
            , 'prop_Types_ISpec_serialisation
1376
            , 'prop_Types_IPolicy_serialisation
1377
            , 'prop_Types_EvacMode_serialisation
1378
            , 'prop_Types_opToResult
1379
            , 'prop_Types_eitherToResult
1380
            ]