Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 7806125e

History | View | Annotate | Download (52.2 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
-- | All disk templates (used later)
94
allDiskTemplates :: [Types.DiskTemplate]
95
allDiskTemplates = [minBound..maxBound]
96

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

    
120

    
121
defGroup :: Group.Group
122
defGroup = flip Group.setIdx 0 $
123
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
124
                  nullIPolicy
125

    
126
defGroupList :: Group.List
127
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
128

    
129
defGroupAssoc :: Data.Map.Map String Types.Gdx
130
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
131

    
132
-- * Helper functions
133

    
134
-- | Simple checker for whether OpResult is fail or pass.
135
isFailure :: Types.OpResult a -> Bool
136
isFailure (Types.OpFail _) = True
137
isFailure _ = False
138

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

    
146
-- | Show a message and fail the test.
147
failTest :: String -> Property
148
failTest msg = printTestCase msg False
149

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

    
157
-- | Check if an instance is smaller than a node.
158
isInstanceSmallerThanNode node inst =
159
  Instance.mem inst   <= Node.availMem node `div` 2 &&
160
  Instance.dsk inst   <= Node.availDisk node `div` 2 &&
161
  Instance.vcpus inst <= Node.availCpu node `div` 2
162

    
163
-- | Create an instance given its spec.
164
createInstance mem dsk vcpus =
165
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
166
    Types.DTDrbd8
167

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

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

    
188
-- | Checks if a node is "big" enough.
189
isNodeBig :: Int -> Node.Node -> Bool
190
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
191
                      && Node.availMem node > size * Types.unitMem
192
                      && Node.availCpu node > size * Types.unitCpu
193

    
194
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
195
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
196

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

    
216
-- | Generates a list of a given size with non-duplicate elements.
217
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
218
genUniquesList cnt =
219
  foldM (\lst _ -> do
220
           newelem <- arbitrary `suchThat` (`notElem` lst)
221
           return (newelem:lst)) [] [1..cnt]
222

    
223
-- * Arbitrary instances
224

    
225
-- | Defines a DNS name.
226
newtype DNSChar = DNSChar { dnsGetChar::Char }
227

    
228
instance Arbitrary DNSChar where
229
  arbitrary = do
230
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
231
    return (DNSChar x)
232

    
233
-- | Generates a single name component.
234
getName :: Gen String
235
getName = do
236
  n <- choose (1, 64)
237
  dn <- vector n::Gen [DNSChar]
238
  return (map dnsGetChar dn)
239

    
240
-- | Generates an entire FQDN.
241
getFQDN :: Gen String
242
getFQDN = do
243
  ncomps <- choose (1, 4)
244
  names <- mapM (const getName) [1..ncomps::Int]
245
  return $ intercalate "." names
246

    
247
-- | Defines a tag type.
248
newtype TagChar = TagChar { tagGetChar :: Char }
249

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

    
255
instance Arbitrary TagChar where
256
  arbitrary = do
257
    c <- elements tagChar
258
    return (TagChar c)
259

    
260
-- | Generates a tag
261
genTag :: Gen [TagChar]
262
genTag = do
263
  -- the correct value would be C.maxTagLen, but that's way too
264
  -- verbose in unittests, and at the moment I don't see any possible
265
  -- bugs with longer tags and the way we use tags in htools
266
  n <- choose (1, 10)
267
  vector n
268

    
269
-- | Generates a list of tags (correctly upper bounded).
270
genTags :: Gen [String]
271
genTags = do
272
  -- the correct value would be C.maxTagsPerObj, but per the comment
273
  -- in genTag, we don't use tags enough in htools to warrant testing
274
  -- such big values
275
  n <- choose (0, 10::Int)
276
  tags <- mapM (const genTag) [1..n]
277
  return $ map (map tagGetChar) tags
278

    
279
instance Arbitrary Types.InstanceStatus where
280
    arbitrary = elements [minBound..maxBound]
281

    
282
-- let's generate a random instance
283
instance Arbitrary Instance.Instance where
284
  arbitrary = do
285
    name <- getFQDN
286
    mem <- choose (0, maxMem)
287
    dsk <- choose (0, maxDsk)
288
    run_st <- arbitrary
289
    pn <- arbitrary
290
    sn <- arbitrary
291
    vcpus <- choose (0, maxCpu)
292
    return $ Instance.create name mem dsk vcpus run_st [] True pn sn
293
              Types.DTDrbd8
294

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

    
326
-- | Helper function to generate a sane node.
327
genOnlineNode :: Gen Node.Node
328
genOnlineNode = do
329
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
330
                              not (Node.failN1 n) &&
331
                              Node.availDisk n > 0 &&
332
                              Node.availMem n > 0 &&
333
                              Node.availCpu n > 0)
334

    
335
-- and a random node
336
instance Arbitrary Node.Node where
337
  arbitrary = genNode Nothing Nothing
338

    
339
-- replace disks
340
instance Arbitrary OpCodes.ReplaceDisksMode where
341
  arbitrary = elements [minBound..maxBound]
342

    
343
instance Arbitrary OpCodes.OpCode where
344
  arbitrary = do
345
    op_id <- elements [ "OP_TEST_DELAY"
346
                      , "OP_INSTANCE_REPLACE_DISKS"
347
                      , "OP_INSTANCE_FAILOVER"
348
                      , "OP_INSTANCE_MIGRATE"
349
                      ]
350
    case op_id of
351
      "OP_TEST_DELAY" ->
352
        liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
353
      "OP_INSTANCE_REPLACE_DISKS" ->
354
        liftM5 OpCodes.OpInstanceReplaceDisks arbitrary arbitrary
355
          arbitrary arbitrary arbitrary
356
      "OP_INSTANCE_FAILOVER" ->
357
        liftM3 OpCodes.OpInstanceFailover arbitrary arbitrary
358
          arbitrary
359
      "OP_INSTANCE_MIGRATE" ->
360
        liftM5 OpCodes.OpInstanceMigrate arbitrary arbitrary
361
          arbitrary arbitrary arbitrary
362
      _ -> fail "Wrong opcode"
363

    
364
instance Arbitrary Jobs.OpStatus where
365
  arbitrary = elements [minBound..maxBound]
366

    
367
instance Arbitrary Jobs.JobStatus where
368
  arbitrary = elements [minBound..maxBound]
369

    
370
newtype SmallRatio = SmallRatio Double deriving Show
371
instance Arbitrary SmallRatio where
372
  arbitrary = do
373
    v <- choose (0, 1)
374
    return $ SmallRatio v
375

    
376
instance Arbitrary Types.AllocPolicy where
377
  arbitrary = elements [minBound..maxBound]
378

    
379
instance Arbitrary Types.DiskTemplate where
380
  arbitrary = elements [minBound..maxBound]
381

    
382
instance Arbitrary Types.FailMode where
383
  arbitrary = elements [minBound..maxBound]
384

    
385
instance Arbitrary Types.EvacMode where
386
  arbitrary = elements [minBound..maxBound]
387

    
388
instance Arbitrary a => Arbitrary (Types.OpResult a) where
389
  arbitrary = arbitrary >>= \c ->
390
              if c
391
                then liftM Types.OpGood arbitrary
392
                else liftM Types.OpFail arbitrary
393

    
394
instance Arbitrary Types.ISpec where
395
  arbitrary = do
396
    mem_s <- arbitrary::Gen (NonNegative Int)
397
    dsk_c <- arbitrary::Gen (NonNegative Int)
398
    dsk_s <- arbitrary::Gen (NonNegative Int)
399
    cpu_c <- arbitrary::Gen (NonNegative Int)
400
    nic_c <- arbitrary::Gen (NonNegative Int)
401
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
402
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
403
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
404
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
405
                       , Types.iSpecNicCount   = fromIntegral nic_c
406
                       }
407

    
408
-- | Generates an ispec bigger than the given one.
409
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
410
genBiggerISpec imin = do
411
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
412
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
413
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
414
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
415
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
416
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
417
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
418
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
419
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
420
                     , Types.iSpecNicCount   = fromIntegral nic_c
421
                     }
422

    
423
instance Arbitrary Types.IPolicy where
424
  arbitrary = do
425
    imin <- arbitrary
426
    istd <- genBiggerISpec imin
427
    imax <- genBiggerISpec istd
428
    num_tmpl <- choose (0, length allDiskTemplates)
429
    dts  <- genUniquesList num_tmpl
430
    return Types.IPolicy { Types.iPolicyMinSpec = imin
431
                         , Types.iPolicyStdSpec = istd
432
                         , Types.iPolicyMaxSpec = imax
433
                         , Types.iPolicyDiskTemplates = dts
434
                         }
435

    
436
-- * Actual tests
437

    
438
-- ** Utils tests
439

    
440
-- | If the list is not just an empty element, and if the elements do
441
-- not contain commas, then join+split should be idempotent.
442
prop_Utils_commaJoinSplit =
443
  forAll (arbitrary `suchThat`
444
          (\l -> l /= [""] && all (notElem ',') l )) $ \lst ->
445
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
446

    
447
-- | Split and join should always be idempotent.
448
prop_Utils_commaSplitJoin s =
449
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
450

    
451
-- | fromObjWithDefault, we test using the Maybe monad and an integer
452
-- value.
453
prop_Utils_fromObjWithDefault def_value random_key =
454
  -- a missing key will be returned with the default
455
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
456
  -- a found key will be returned as is, not with default
457
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
458
       random_key (def_value+1) == Just def_value
459
    where _types = def_value :: Integer
460

    
461
-- | Test that functional if' behaves like the syntactic sugar if.
462
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
463
prop_Utils_if'if cnd a b =
464
  Utils.if' cnd a b ==? if cnd then a else b
465

    
466
-- | Test basic select functionality
467
prop_Utils_select :: Int      -- ^ Default result
468
                  -> [Int]    -- ^ List of False values
469
                  -> [Int]    -- ^ List of True values
470
                  -> Gen Prop -- ^ Test result
471
prop_Utils_select def lst1 lst2 =
472
  Utils.select def (flist ++ tlist) ==? expectedresult
473
    where expectedresult = Utils.if' (null lst2) def (head lst2)
474
          flist = zip (repeat False) lst1
475
          tlist = zip (repeat True)  lst2
476

    
477
-- | Test basic select functionality with undefined default
478
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
479
                         -> NonEmptyList Int -- ^ List of True values
480
                         -> Gen Prop         -- ^ Test result
481
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
482
  Utils.select undefined (flist ++ tlist) ==? head lst2
483
    where flist = zip (repeat False) lst1
484
          tlist = zip (repeat True)  lst2
485

    
486
-- | Test basic select functionality with undefined list values
487
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
488
                         -> NonEmptyList Int -- ^ List of True values
489
                         -> Gen Prop         -- ^ Test result
490
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
491
  Utils.select undefined cndlist ==? head lst2
492
    where flist = zip (repeat False) lst1
493
          tlist = zip (repeat True)  lst2
494
          cndlist = flist ++ tlist ++ [undefined]
495

    
496
prop_Utils_parseUnit (NonNegative n) =
497
  Utils.parseUnit (show n) == Types.Ok n &&
498
  Utils.parseUnit (show n ++ "m") == Types.Ok n &&
499
  (case Utils.parseUnit (show n ++ "M") of
500
     Types.Ok m -> if n > 0
501
                     then m < n  -- for positive values, X MB is < than X MiB
502
                     else m == 0 -- but for 0, 0 MB == 0 MiB
503
     Types.Bad _ -> False) &&
504
  Utils.parseUnit (show n ++ "g") == Types.Ok (n*1024) &&
505
  Utils.parseUnit (show n ++ "t") == Types.Ok (n*1048576) &&
506
  Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int)
507
    where _types = n::Int
508

    
509
-- | Test list for the Utils module.
510
testSuite "Utils"
511
            [ 'prop_Utils_commaJoinSplit
512
            , 'prop_Utils_commaSplitJoin
513
            , 'prop_Utils_fromObjWithDefault
514
            , 'prop_Utils_if'if
515
            , 'prop_Utils_select
516
            , 'prop_Utils_select_undefd
517
            , 'prop_Utils_select_undefv
518
            , 'prop_Utils_parseUnit
519
            ]
520

    
521
-- ** PeerMap tests
522

    
523
-- | Make sure add is idempotent.
524
prop_PeerMap_addIdempotent pmap key em =
525
  fn puniq ==? fn (fn puniq)
526
    where _types = (pmap::PeerMap.PeerMap,
527
                    key::PeerMap.Key, em::PeerMap.Elem)
528
          fn = PeerMap.add key em
529
          puniq = PeerMap.accumArray const pmap
530

    
531
-- | Make sure remove is idempotent.
532
prop_PeerMap_removeIdempotent pmap key =
533
  fn puniq ==? fn (fn puniq)
534
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
535
          fn = PeerMap.remove key
536
          puniq = PeerMap.accumArray const pmap
537

    
538
-- | Make sure a missing item returns 0.
539
prop_PeerMap_findMissing pmap key =
540
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
541
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
542
          puniq = PeerMap.accumArray const pmap
543

    
544
-- | Make sure an added item is found.
545
prop_PeerMap_addFind pmap key em =
546
  PeerMap.find key (PeerMap.add key em puniq) ==? em
547
    where _types = (pmap::PeerMap.PeerMap,
548
                    key::PeerMap.Key, em::PeerMap.Elem)
549
          puniq = PeerMap.accumArray const pmap
550

    
551
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
552
prop_PeerMap_maxElem pmap =
553
  PeerMap.maxElem puniq ==? if null puniq then 0
554
                              else (maximum . snd . unzip) puniq
555
    where _types = pmap::PeerMap.PeerMap
556
          puniq = PeerMap.accumArray const pmap
557

    
558
-- | List of tests for the PeerMap module.
559
testSuite "PeerMap"
560
            [ 'prop_PeerMap_addIdempotent
561
            , 'prop_PeerMap_removeIdempotent
562
            , 'prop_PeerMap_maxElem
563
            , 'prop_PeerMap_addFind
564
            , 'prop_PeerMap_findMissing
565
            ]
566

    
567
-- ** Container tests
568

    
569
-- we silence the following due to hlint bug fixed in later versions
570
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
571
prop_Container_addTwo cdata i1 i2 =
572
  fn i1 i2 cont == fn i2 i1 cont &&
573
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
574
    where _types = (cdata::[Int],
575
                    i1::Int, i2::Int)
576
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
577
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
578

    
579
prop_Container_nameOf node =
580
  let nl = makeSmallCluster node 1
581
      fnode = head (Container.elems nl)
582
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
583

    
584
-- | We test that in a cluster, given a random node, we can find it by
585
-- its name and alias, as long as all names and aliases are unique,
586
-- and that we fail to find a non-existing name.
587
prop_Container_findByName node =
588
  forAll (choose (1, 20)) $ \ cnt ->
589
  forAll (choose (0, cnt - 1)) $ \ fidx ->
590
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
591
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
592
  let names = zip (take cnt allnames) (drop cnt allnames)
593
      nl = makeSmallCluster node cnt
594
      nodes = Container.elems nl
595
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
596
                                             nn { Node.name = name,
597
                                                  Node.alias = alias }))
598
               $ zip names nodes
599
      nl' = Container.fromList nodes'
600
      target = snd (nodes' !! fidx)
601
  in Container.findByName nl' (Node.name target) == Just target &&
602
     Container.findByName nl' (Node.alias target) == Just target &&
603
     isNothing (Container.findByName nl' othername)
604

    
605
testSuite "Container"
606
            [ 'prop_Container_addTwo
607
            , 'prop_Container_nameOf
608
            , 'prop_Container_findByName
609
            ]
610

    
611
-- ** Instance tests
612

    
613
-- Simple instance tests, we only have setter/getters
614

    
615
prop_Instance_creat inst =
616
  Instance.name inst ==? Instance.alias inst
617

    
618
prop_Instance_setIdx inst idx =
619
  Instance.idx (Instance.setIdx inst idx) ==? idx
620
    where _types = (inst::Instance.Instance, idx::Types.Idx)
621

    
622
prop_Instance_setName inst name =
623
  Instance.name newinst == name &&
624
  Instance.alias newinst == name
625
    where _types = (inst::Instance.Instance, name::String)
626
          newinst = Instance.setName inst name
627

    
628
prop_Instance_setAlias inst name =
629
  Instance.name newinst == Instance.name inst &&
630
  Instance.alias newinst == name
631
    where _types = (inst::Instance.Instance, name::String)
632
          newinst = Instance.setAlias inst name
633

    
634
prop_Instance_setPri inst pdx =
635
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
636
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
637

    
638
prop_Instance_setSec inst sdx =
639
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
640
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
641

    
642
prop_Instance_setBoth inst pdx sdx =
643
  Instance.pNode si == pdx && Instance.sNode si == sdx
644
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
645
          si = Instance.setBoth inst pdx sdx
646

    
647
prop_Instance_shrinkMG inst =
648
  Instance.mem inst >= 2 * Types.unitMem ==>
649
    case Instance.shrinkByType inst Types.FailMem of
650
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
651
      _ -> False
652

    
653
prop_Instance_shrinkMF inst =
654
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
655
    let inst' = inst { Instance.mem = mem}
656
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
657

    
658
prop_Instance_shrinkCG inst =
659
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
660
    case Instance.shrinkByType inst Types.FailCPU of
661
      Types.Ok inst' ->
662
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
663
      _ -> False
664

    
665
prop_Instance_shrinkCF inst =
666
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
667
    let inst' = inst { Instance.vcpus = vcpus }
668
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
669

    
670
prop_Instance_shrinkDG inst =
671
  Instance.dsk inst >= 2 * Types.unitDsk ==>
672
    case Instance.shrinkByType inst Types.FailDisk of
673
      Types.Ok inst' ->
674
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
675
      _ -> False
676

    
677
prop_Instance_shrinkDF inst =
678
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
679
    let inst' = inst { Instance.dsk = dsk }
680
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
681

    
682
prop_Instance_setMovable inst m =
683
  Instance.movable inst' ==? m
684
    where inst' = Instance.setMovable inst m
685

    
686
testSuite "Instance"
687
            [ 'prop_Instance_creat
688
            , 'prop_Instance_setIdx
689
            , 'prop_Instance_setName
690
            , 'prop_Instance_setAlias
691
            , 'prop_Instance_setPri
692
            , 'prop_Instance_setSec
693
            , 'prop_Instance_setBoth
694
            , 'prop_Instance_shrinkMG
695
            , 'prop_Instance_shrinkMF
696
            , 'prop_Instance_shrinkCG
697
            , 'prop_Instance_shrinkCF
698
            , 'prop_Instance_shrinkDG
699
            , 'prop_Instance_shrinkDF
700
            , 'prop_Instance_setMovable
701
            ]
702

    
703
-- ** Text backend tests
704

    
705
-- Instance text loader tests
706

    
707
prop_Text_Load_Instance name mem dsk vcpus status
708
                        (NonEmpty pnode) snode
709
                        (NonNegative pdx) (NonNegative sdx) autobal dt =
710
  pnode /= snode && pdx /= sdx ==>
711
  let vcpus_s = show vcpus
712
      dsk_s = show dsk
713
      mem_s = show mem
714
      status_s = Types.instanceStatusToRaw status
715
      ndx = if null snode
716
              then [(pnode, pdx)]
717
              else [(pnode, pdx), (snode, sdx)]
718
      nl = Data.Map.fromList ndx
719
      tags = ""
720
      sbal = if autobal then "Y" else "N"
721
      sdt = Types.diskTemplateToRaw dt
722
      inst = Text.loadInst nl
723
             [name, mem_s, dsk_s, vcpus_s, status_s,
724
              sbal, pnode, snode, sdt, tags]
725
      fail1 = Text.loadInst nl
726
              [name, mem_s, dsk_s, vcpus_s, status_s,
727
               sbal, pnode, pnode, tags]
728
      _types = ( name::String, mem::Int, dsk::Int
729
               , vcpus::Int, status::Types.InstanceStatus
730
               , snode::String
731
               , autobal::Bool)
732
  in case inst of
733
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
734
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
735
                                        \ loading the instance" $
736
               Instance.name i == name &&
737
               Instance.vcpus i == vcpus &&
738
               Instance.mem i == mem &&
739
               Instance.pNode i == pdx &&
740
               Instance.sNode i == (if null snode
741
                                      then Node.noSecondary
742
                                      else sdx) &&
743
               Instance.autoBalance i == autobal &&
744
               Types.isBad fail1
745

    
746
prop_Text_Load_InstanceFail ktn fields =
747
  length fields /= 10 ==>
748
    case Text.loadInst nl fields of
749
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
750
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
751
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
752
    where nl = Data.Map.fromList ktn
753

    
754
prop_Text_Load_Node name tm nm fm td fd tc fo =
755
  let conv v = if v < 0
756
                 then "?"
757
                 else show v
758
      tm_s = conv tm
759
      nm_s = conv nm
760
      fm_s = conv fm
761
      td_s = conv td
762
      fd_s = conv fd
763
      tc_s = conv tc
764
      fo_s = if fo
765
               then "Y"
766
               else "N"
767
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
768
      gid = Group.uuid defGroup
769
  in case Text.loadNode defGroupAssoc
770
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
771
       Nothing -> False
772
       Just (name', node) ->
773
         if fo || any_broken
774
           then Node.offline node
775
           else Node.name node == name' && name' == name &&
776
                Node.alias node == name &&
777
                Node.tMem node == fromIntegral tm &&
778
                Node.nMem node == nm &&
779
                Node.fMem node == fm &&
780
                Node.tDsk node == fromIntegral td &&
781
                Node.fDsk node == fd &&
782
                Node.tCpu node == fromIntegral tc
783

    
784
prop_Text_Load_NodeFail fields =
785
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
786

    
787
prop_Text_NodeLSIdempotent node =
788
  (Text.loadNode defGroupAssoc.
789
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==
790
  Just (Node.name n, n)
791
    -- override failN1 to what loadNode returns by default
792
    where n = node { Node.failN1 = True, Node.offline = False
793
                   , Node.iPolicy = Types.defIPolicy }
794

    
795
prop_Text_ISpecIdempotent ispec =
796
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
797
       Text.serializeISpec $ ispec of
798
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
799
    Types.Ok ispec' -> ispec ==? ispec'
800

    
801
prop_Text_IPolicyIdempotent ipol =
802
  case Text.loadIPolicy . Utils.sepSplit '|' $
803
       Text.serializeIPolicy owner ipol of
804
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
805
    Types.Ok res -> (owner, ipol) ==? res
806
  where owner = "dummy"
807

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

    
843
testSuite "Text"
844
            [ 'prop_Text_Load_Instance
845
            , 'prop_Text_Load_InstanceFail
846
            , 'prop_Text_Load_Node
847
            , 'prop_Text_Load_NodeFail
848
            , 'prop_Text_NodeLSIdempotent
849
            , 'prop_Text_ISpecIdempotent
850
            , 'prop_Text_IPolicyIdempotent
851
            , 'prop_Text_CreateSerialise
852
            ]
853

    
854
-- ** Node tests
855

    
856
prop_Node_setAlias node name =
857
  Node.name newnode == Node.name node &&
858
  Node.alias newnode == name
859
    where _types = (node::Node.Node, name::String)
860
          newnode = Node.setAlias node name
861

    
862
prop_Node_setOffline node status =
863
  Node.offline newnode ==? status
864
    where newnode = Node.setOffline node status
865

    
866
prop_Node_setXmem node xm =
867
  Node.xMem newnode ==? xm
868
    where newnode = Node.setXmem node xm
869

    
870
prop_Node_setMcpu node mc =
871
  Node.mCpu newnode ==? mc
872
    where newnode = Node.setMcpu node mc
873

    
874
-- | Check that an instance add with too high memory or disk will be
875
-- rejected.
876
prop_Node_addPriFM node inst =
877
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
878
  not (Instance.instanceOffline inst) ==>
879
  case Node.addPri node inst'' of
880
    Types.OpFail Types.FailMem -> True
881
    _ -> False
882
  where _types = (node::Node.Node, inst::Instance.Instance)
883
        inst' = setInstanceSmallerThanNode node inst
884
        inst'' = inst' { Instance.mem = Instance.mem inst }
885

    
886
prop_Node_addPriFD node inst =
887
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
888
    case Node.addPri node inst'' of
889
      Types.OpFail Types.FailDisk -> True
890
      _ -> False
891
    where _types = (node::Node.Node, inst::Instance.Instance)
892
          inst' = setInstanceSmallerThanNode node inst
893
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
894

    
895
prop_Node_addPriFC (Positive extra) =
896
  forAll genOnlineNode $ \node ->
897
  forAll (arbitrary `suchThat` Instance.instanceNotOffline) $ \inst ->
898
  let inst' = setInstanceSmallerThanNode node inst
899
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
900
  in case Node.addPri node inst'' of
901
       Types.OpFail Types.FailCPU -> property True
902
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
903

    
904
-- | Check that an instance add with too high memory or disk will be
905
-- rejected.
906
prop_Node_addSec node inst pdx =
907
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
908
    not (Instance.instanceOffline inst)) ||
909
   Instance.dsk inst >= Node.fDsk node) &&
910
  not (Node.failN1 node) ==>
911
      isFailure (Node.addSec node inst pdx)
912
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
913

    
914
-- | Check that an offline instance with reasonable disk size can always
915
-- be added.
916
prop_Node_addPriOffline =
917
  forAll (arbitrary `suchThat` ((> 0) . Node.fMem)) $ \node ->
918
  forAll (arbitrary `suchThat`
919
          (\ x ->  (Instance.dsk x  < Node.fDsk node) &&
920
                   Instance.instanceOffline x)) $ \inst ->
921
  case Node.addPri node inst of
922
    Types.OpGood _ -> True
923
    _ -> False
924

    
925
prop_Node_addSecOffline pdx =
926
  forAll genOnlineNode $ \node ->
927
  forAll (arbitrary `suchThat`
928
          (\ inst -> Instance.dsk inst  < Node.availDisk node)) $ \inst ->
929
  case Node.addSec node (inst { Instance.runSt = Types.AdminOffline }) pdx of
930
    Types.OpGood _ -> True
931
    _ -> False
932

    
933
-- | Checks for memory reservation changes.
934
prop_Node_rMem inst =
935
  not (Instance.instanceOffline inst) ==>
936
  forAll (arbitrary `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
937
  -- ab = auto_balance, nb = non-auto_balance
938
  -- we use -1 as the primary node of the instance
939
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True }
940
      inst_ab = setInstanceSmallerThanNode node inst'
941
      inst_nb = inst_ab { Instance.autoBalance = False }
942
      -- now we have the two instances, identical except the
943
      -- autoBalance attribute
944
      orig_rmem = Node.rMem node
945
      inst_idx = Instance.idx inst_ab
946
      node_add_ab = Node.addSec node inst_ab (-1)
947
      node_add_nb = Node.addSec node inst_nb (-1)
948
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
949
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
950
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
951
       (Types.OpGood a_ab, Types.OpGood a_nb,
952
        Types.OpGood d_ab, Types.OpGood d_nb) ->
953
         printTestCase "Consistency checks failed" $
954
           Node.rMem a_ab >  orig_rmem &&
955
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
956
           Node.rMem a_nb == orig_rmem &&
957
           Node.rMem d_ab == orig_rmem &&
958
           Node.rMem d_nb == orig_rmem &&
959
           -- this is not related to rMem, but as good a place to
960
           -- test as any
961
           inst_idx `elem` Node.sList a_ab &&
962
           inst_idx `notElem` Node.sList d_ab
963
       x -> failTest $ "Failed to add/remove instances: " ++ show x
964

    
965
-- | Check mdsk setting.
966
prop_Node_setMdsk node mx =
967
  Node.loDsk node' >= 0 &&
968
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
969
  Node.availDisk node' >= 0 &&
970
  Node.availDisk node' <= Node.fDsk node' &&
971
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
972
  Node.mDsk node' == mx'
973
    where _types = (node::Node.Node, mx::SmallRatio)
974
          node' = Node.setMdsk node mx'
975
          SmallRatio mx' = mx
976

    
977
-- Check tag maps
978
prop_Node_tagMaps_idempotent tags =
979
  Node.delTags (Node.addTags m tags) tags ==? m
980
    where m = Data.Map.empty
981

    
982
prop_Node_tagMaps_reject tags =
983
  not (null tags) ==>
984
  all (\t -> Node.rejectAddTags m [t]) tags
985
    where m = Node.addTags Data.Map.empty tags
986

    
987
prop_Node_showField node =
988
  forAll (elements Node.defaultFields) $ \ field ->
989
  fst (Node.showHeader field) /= Types.unknownField &&
990
  Node.showField node field /= Types.unknownField
991

    
992
prop_Node_computeGroups nodes =
993
  let ng = Node.computeGroups nodes
994
      onlyuuid = map fst ng
995
  in length nodes == sum (map (length . snd) ng) &&
996
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
997
     length (nub onlyuuid) == length onlyuuid &&
998
     (null nodes || not (null ng))
999

    
1000
testSuite "Node"
1001
            [ 'prop_Node_setAlias
1002
            , 'prop_Node_setOffline
1003
            , 'prop_Node_setMcpu
1004
            , 'prop_Node_setXmem
1005
            , 'prop_Node_addPriFM
1006
            , 'prop_Node_addPriFD
1007
            , 'prop_Node_addPriFC
1008
            , 'prop_Node_addSec
1009
            , 'prop_Node_addPriOffline
1010
            , 'prop_Node_addSecOffline
1011
            , 'prop_Node_rMem
1012
            , 'prop_Node_setMdsk
1013
            , 'prop_Node_tagMaps_idempotent
1014
            , 'prop_Node_tagMaps_reject
1015
            , 'prop_Node_showField
1016
            , 'prop_Node_computeGroups
1017
            ]
1018

    
1019
-- ** Cluster tests
1020

    
1021
-- | Check that the cluster score is close to zero for a homogeneous
1022
-- cluster.
1023
prop_Score_Zero node =
1024
  forAll (choose (1, 1024)) $ \count ->
1025
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1026
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1027
  let fn = Node.buildPeers node Container.empty
1028
      nlst = replicate count fn
1029
      score = Cluster.compCVNodes nlst
1030
  -- we can't say == 0 here as the floating point errors accumulate;
1031
  -- this should be much lower than the default score in CLI.hs
1032
  in score <= 1e-12
1033

    
1034
-- | Check that cluster stats are sane.
1035
prop_CStats_sane =
1036
  forAll (choose (1, 1024)) $ \count ->
1037
  forAll genOnlineNode $ \node ->
1038
  let fn = Node.buildPeers node Container.empty
1039
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1040
      nl = Container.fromList nlst
1041
      cstats = Cluster.totalResources nl
1042
  in Cluster.csAdsk cstats >= 0 &&
1043
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1044

    
1045
-- | Check that one instance is allocated correctly, without
1046
-- rebalances needed.
1047
prop_ClusterAlloc_sane inst =
1048
  forAll (choose (5, 20)) $ \count ->
1049
  forAll genOnlineNode $ \node ->
1050
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1051
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
1052
     Cluster.tryAlloc nl il inst' of
1053
       Types.Bad _ -> False
1054
       Types.Ok as ->
1055
         case Cluster.asSolution as of
1056
           Nothing -> False
1057
           Just (xnl, xi, _, cv) ->
1058
             let il' = Container.add (Instance.idx xi) xi il
1059
                 tbl = Cluster.Table xnl il' cv []
1060
             in not (canBalance tbl True True False)
1061

    
1062
-- | Checks that on a 2-5 node cluster, we can allocate a random
1063
-- instance spec via tiered allocation (whatever the original instance
1064
-- spec), on either one or two nodes.
1065
prop_ClusterCanTieredAlloc inst =
1066
  forAll (choose (2, 5)) $ \count ->
1067
  forAll (choose (1, 2)) $ \rqnodes ->
1068
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1069
  let nl = makeSmallCluster node count
1070
      il = Container.empty
1071
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1072
  in case allocnodes >>= \allocnodes' ->
1073
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1074
       Types.Bad _ -> False
1075
       Types.Ok (_, _, il', ixes, cstats) -> not (null ixes) &&
1076
                                             IntMap.size il' == length ixes &&
1077
                                             length ixes == length cstats
1078

    
1079
-- | Helper function to create a cluster with the given range of nodes
1080
-- and allocate an instance on it.
1081
genClusterAlloc count node inst =
1082
  let nl = makeSmallCluster node count
1083
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
1084
     Cluster.tryAlloc nl Container.empty inst of
1085
       Types.Bad _ -> Types.Bad "Can't allocate"
1086
       Types.Ok as ->
1087
         case Cluster.asSolution as of
1088
           Nothing -> Types.Bad "Empty solution?"
1089
           Just (xnl, xi, _, _) ->
1090
             let xil = Container.add (Instance.idx xi) xi Container.empty
1091
             in Types.Ok (xnl, xil, xi)
1092

    
1093
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1094
-- we can also relocate it.
1095
prop_ClusterAllocRelocate =
1096
  forAll (choose (4, 8)) $ \count ->
1097
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1098
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1099
  case genClusterAlloc count node inst of
1100
    Types.Bad msg -> failTest msg
1101
    Types.Ok (nl, il, inst') ->
1102
      case IAlloc.processRelocate defGroupList nl il
1103
             (Instance.idx inst) 1 [Instance.sNode inst'] of
1104
        Types.Ok _ -> printTestCase "??" True  -- huh, how to make
1105
                                               -- this nicer...
1106
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1107

    
1108
-- | Helper property checker for the result of a nodeEvac or
1109
-- changeGroup operation.
1110
check_EvacMode grp inst result =
1111
  case result of
1112
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1113
    Types.Ok (_, _, es) ->
1114
      let moved = Cluster.esMoved es
1115
          failed = Cluster.esFailed es
1116
          opcodes = not . null $ Cluster.esOpCodes es
1117
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1118
         failmsg "'opcodes' is null" opcodes .&&.
1119
         case moved of
1120
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1121
                               .&&.
1122
                               failmsg "wrong target group"
1123
                                         (gdx == Group.idx grp)
1124
           v -> failmsg  ("invalid solution: " ++ show v) False
1125
  where failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1126
        idx = Instance.idx inst
1127

    
1128
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1129
-- we can also node-evacuate it.
1130
prop_ClusterAllocEvacuate =
1131
  forAll (choose (4, 8)) $ \count ->
1132
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1133
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1134
  case genClusterAlloc count node inst of
1135
    Types.Bad msg -> failTest msg
1136
    Types.Ok (nl, il, inst') ->
1137
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1138
                              Cluster.tryNodeEvac defGroupList nl il mode
1139
                                [Instance.idx inst']) [minBound..maxBound]
1140

    
1141
-- | Checks that on a 4-8 node cluster with two node groups, once we
1142
-- allocate an instance on the first node group, we can also change
1143
-- its group.
1144
prop_ClusterAllocChangeGroup =
1145
  forAll (choose (4, 8)) $ \count ->
1146
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1147
  forAll (arbitrary `suchThat` (isInstanceSmallerThanNode node)) $ \inst ->
1148
  case genClusterAlloc count node inst of
1149
    Types.Bad msg -> failTest msg
1150
    Types.Ok (nl, il, inst') ->
1151
      -- we need to add a second node group and nodes to the cluster
1152
      let nl2 = Container.elems $ makeSmallCluster node count
1153
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1154
          maxndx = maximum . map Node.idx $ nl2
1155
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1156
                             , Node.idx = Node.idx n + maxndx }) nl2
1157
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1158
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1159
          nl' = IntMap.union nl nl4
1160
      in check_EvacMode grp2 inst' $
1161
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1162

    
1163
-- | Check that allocating multiple instances on a cluster, then
1164
-- adding an empty node, results in a valid rebalance.
1165
prop_ClusterAllocBalance =
1166
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1167
  forAll (choose (3, 5)) $ \count ->
1168
  not (Node.offline node) && not (Node.failN1 node) ==>
1169
  let nl = makeSmallCluster node count
1170
      (hnode, nl') = IntMap.deleteFindMax nl
1171
      il = Container.empty
1172
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1173
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1174
  in case allocnodes >>= \allocnodes' ->
1175
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1176
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1177
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1178
       Types.Ok (_, xnl, il', _, _) ->
1179
         let ynl = Container.add (Node.idx hnode) hnode xnl
1180
             cv = Cluster.compCV ynl
1181
             tbl = Cluster.Table ynl il' cv []
1182
         in printTestCase "Failed to rebalance" $
1183
            canBalance tbl True True False
1184

    
1185
-- | Checks consistency.
1186
prop_ClusterCheckConsistency node inst =
1187
  let nl = makeSmallCluster node 3
1188
      [node1, node2, node3] = Container.elems nl
1189
      node3' = node3 { Node.group = 1 }
1190
      nl' = Container.add (Node.idx node3') node3' nl
1191
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1192
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1193
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1194
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1195
  in null (ccheck [(0, inst1)]) &&
1196
     null (ccheck [(0, inst2)]) &&
1197
     (not . null $ ccheck [(0, inst3)])
1198

    
1199
-- | For now, we only test that we don't lose instances during the split.
1200
prop_ClusterSplitCluster node inst =
1201
  forAll (choose (0, 100)) $ \icnt ->
1202
  let nl = makeSmallCluster node 2
1203
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1204
                   (nl, Container.empty) [1..icnt]
1205
      gni = Cluster.splitCluster nl' il'
1206
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1207
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1208
                                 (Container.elems nl'')) gni
1209

    
1210
-- | Helper function to check if we can allocate an instance on a
1211
-- given node list.
1212
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1213
canAllocOn nl reqnodes inst =
1214
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1215
       Cluster.tryAlloc nl (Container.empty) inst of
1216
       Types.Bad _ -> False
1217
       Types.Ok as ->
1218
         case Cluster.asSolution as of
1219
           Nothing -> False
1220
           Just _ -> True
1221

    
1222
-- | Checks that allocation obeys minimum and maximum instance
1223
-- policies. The unittest generates a random node, duplicates it count
1224
-- times, and generates a random instance that can be allocated on
1225
-- this mini-cluster; it then checks that after applying a policy that
1226
-- the instance doesn't fits, the allocation fails.
1227
prop_ClusterAllocPolicy node =
1228
  -- rqn is the required nodes (1 or 2)
1229
  forAll (choose (1, 2)) $ \rqn ->
1230
  forAll (choose (5, 20)) $ \count ->
1231
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1232
         $ \inst ->
1233
  forAll (arbitrary `suchThat` (isFailure .
1234
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1235
  let node' = Node.setPolicy ipol node
1236
      nl = makeSmallCluster node' count
1237
  in not $ canAllocOn nl rqn inst
1238

    
1239
testSuite "Cluster"
1240
            [ 'prop_Score_Zero
1241
            , 'prop_CStats_sane
1242
            , 'prop_ClusterAlloc_sane
1243
            , 'prop_ClusterCanTieredAlloc
1244
            , 'prop_ClusterAllocRelocate
1245
            , 'prop_ClusterAllocEvacuate
1246
            , 'prop_ClusterAllocChangeGroup
1247
            , 'prop_ClusterAllocBalance
1248
            , 'prop_ClusterCheckConsistency
1249
            , 'prop_ClusterSplitCluster
1250
            , 'prop_ClusterAllocPolicy
1251
            ]
1252

    
1253
-- ** OpCodes tests
1254

    
1255
-- | Check that opcode serialization is idempotent.
1256
prop_OpCodes_serialization op =
1257
  case J.readJSON (J.showJSON op) of
1258
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1259
    J.Ok op' -> op ==? op'
1260
  where _types = op::OpCodes.OpCode
1261

    
1262
testSuite "OpCodes"
1263
            [ 'prop_OpCodes_serialization ]
1264

    
1265
-- ** Jobs tests
1266

    
1267
-- | Check that (queued) job\/opcode status serialization is idempotent.
1268
prop_OpStatus_serialization os =
1269
  case J.readJSON (J.showJSON os) of
1270
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1271
    J.Ok os' -> os ==? os'
1272
  where _types = os::Jobs.OpStatus
1273

    
1274
prop_JobStatus_serialization js =
1275
  case J.readJSON (J.showJSON js) of
1276
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1277
    J.Ok js' -> js ==? js'
1278
  where _types = js::Jobs.JobStatus
1279

    
1280
testSuite "Jobs"
1281
            [ 'prop_OpStatus_serialization
1282
            , 'prop_JobStatus_serialization
1283
            ]
1284

    
1285
-- ** Loader tests
1286

    
1287
prop_Loader_lookupNode ktn inst node =
1288
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1289
    where nl = Data.Map.fromList ktn
1290

    
1291
prop_Loader_lookupInstance kti inst =
1292
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1293
    where il = Data.Map.fromList kti
1294

    
1295
prop_Loader_assignIndices =
1296
  -- generate nodes with unique names
1297
  forAll (arbitrary `suchThat`
1298
          (\nodes ->
1299
             let names = map Node.name nodes
1300
             in length names == length (nub names))) $ \nodes ->
1301
  let (nassoc, kt) =
1302
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1303
  in Data.Map.size nassoc == length nodes &&
1304
     Container.size kt == length nodes &&
1305
     if not (null nodes)
1306
       then maximum (IntMap.keys kt) == length nodes - 1
1307
       else True
1308

    
1309
-- | Checks that the number of primary instances recorded on the nodes
1310
-- is zero.
1311
prop_Loader_mergeData ns =
1312
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1313
  in case Loader.mergeData [] [] [] []
1314
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1315
    Types.Bad _ -> False
1316
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1317
      let nodes = Container.elems nl
1318
          instances = Container.elems il
1319
      in (sum . map (length . Node.pList)) nodes == 0 &&
1320
         null instances
1321

    
1322
-- | Check that compareNameComponent on equal strings works.
1323
prop_Loader_compareNameComponent_equal :: String -> Bool
1324
prop_Loader_compareNameComponent_equal s =
1325
  Loader.compareNameComponent s s ==
1326
    Loader.LookupResult Loader.ExactMatch s
1327

    
1328
-- | Check that compareNameComponent on prefix strings works.
1329
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1330
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1331
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1332
    Loader.LookupResult Loader.PartialMatch s1
1333

    
1334
testSuite "Loader"
1335
            [ 'prop_Loader_lookupNode
1336
            , 'prop_Loader_lookupInstance
1337
            , 'prop_Loader_assignIndices
1338
            , 'prop_Loader_mergeData
1339
            , 'prop_Loader_compareNameComponent_equal
1340
            , 'prop_Loader_compareNameComponent_prefix
1341
            ]
1342

    
1343
-- ** Types tests
1344

    
1345
prop_Types_AllocPolicy_serialisation apol =
1346
  case J.readJSON (J.showJSON apol) of
1347
    J.Ok p -> p ==? apol
1348
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1349
      where _types = apol::Types.AllocPolicy
1350

    
1351
prop_Types_DiskTemplate_serialisation dt =
1352
  case J.readJSON (J.showJSON dt) of
1353
    J.Ok p -> p ==? dt
1354
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1355
      where _types = dt::Types.DiskTemplate
1356

    
1357
prop_Types_ISpec_serialisation ispec =
1358
  case J.readJSON (J.showJSON ispec) of
1359
    J.Ok p -> p ==? ispec
1360
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1361
      where _types = ispec::Types.ISpec
1362

    
1363
prop_Types_IPolicy_serialisation ipol =
1364
  case J.readJSON (J.showJSON ipol) of
1365
    J.Ok p -> p ==? ipol
1366
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1367
      where _types = ipol::Types.IPolicy
1368

    
1369
prop_Types_EvacMode_serialisation em =
1370
  case J.readJSON (J.showJSON em) of
1371
    J.Ok p -> p ==? em
1372
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1373
      where _types = em::Types.EvacMode
1374

    
1375
prop_Types_opToResult op =
1376
  case op of
1377
    Types.OpFail _ -> Types.isBad r
1378
    Types.OpGood v -> case r of
1379
                        Types.Bad _ -> False
1380
                        Types.Ok v' -> v == v'
1381
  where r = Types.opToResult op
1382
        _types = op::Types.OpResult Int
1383

    
1384
prop_Types_eitherToResult ei =
1385
  case ei of
1386
    Left _ -> Types.isBad r
1387
    Right v -> case r of
1388
                 Types.Bad _ -> False
1389
                 Types.Ok v' -> v == v'
1390
    where r = Types.eitherToResult ei
1391
          _types = ei::Either String Int
1392

    
1393
testSuite "Types"
1394
            [ 'prop_Types_AllocPolicy_serialisation
1395
            , 'prop_Types_DiskTemplate_serialisation
1396
            , 'prop_Types_ISpec_serialisation
1397
            , 'prop_Types_IPolicy_serialisation
1398
            , 'prop_Types_EvacMode_serialisation
1399
            , 'prop_Types_opToResult
1400
            , 'prop_Types_eitherToResult
1401
            ]