Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (43.9 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittests for ganeti-htools.
4

    
5
-}
6

    
7
{-
8

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

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

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

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

    
26
-}
27

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

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

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

    
77
import Ganeti.HTools.QCHelper (testSuite)
78

    
79
-- * Constants
80

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

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

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

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

    
116

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

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

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

    
128
-- * Helper functions
129

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

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

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

    
149
-- | Create an instance given its spec.
150
createInstance mem dsk vcpus =
151
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
152
    Types.DTDrbd8
153

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

    
167
-- | Make a small cluster, both nodes and instances.
168
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
169
                      -> (Node.List, Instance.List, Instance.Instance)
170
makeSmallEmptyCluster node count inst =
171
  (makeSmallCluster node count, Container.empty,
172
   setInstanceSmallerThanNode node inst)
173

    
174
-- | Checks if a node is "big" enough.
175
isNodeBig :: Int -> Node.Node -> Bool
176
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
177
                      && Node.availMem node > size * Types.unitMem
178
                      && Node.availCpu node > size * Types.unitCpu
179

    
180
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
181
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
182

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

    
202
-- * Arbitrary instances
203

    
204
-- | Defines a DNS name.
205
newtype DNSChar = DNSChar { dnsGetChar::Char }
206

    
207
instance Arbitrary DNSChar where
208
  arbitrary = do
209
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
210
    return (DNSChar x)
211

    
212
getName :: Gen String
213
getName = do
214
  n <- choose (1, 64)
215
  dn <- vector n::Gen [DNSChar]
216
  return (map dnsGetChar dn)
217

    
218
getFQDN :: Gen String
219
getFQDN = do
220
  felem <- getName
221
  ncomps <- choose (1, 4)
222
  frest <- vector ncomps::Gen [[DNSChar]]
223
  let frest' = map (map dnsGetChar) frest
224
  return (felem ++ "." ++ intercalate "." frest')
225

    
226
instance Arbitrary Types.InstanceStatus where
227
    arbitrary = elements [minBound..maxBound]
228

    
229
-- let's generate a random instance
230
instance Arbitrary Instance.Instance where
231
  arbitrary = do
232
    name <- getFQDN
233
    mem <- choose (0, maxMem)
234
    dsk <- choose (0, maxDsk)
235
    run_st <- arbitrary
236
    pn <- arbitrary
237
    sn <- arbitrary
238
    vcpus <- choose (0, maxCpu)
239
    return $ Instance.create name mem dsk vcpus run_st [] True pn sn
240
              Types.DTDrbd8
241

    
242
-- | Generas an arbitrary node based on sizing information.
243
genNode :: Maybe Int -- ^ Minimum node size in terms of units
244
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
245
                     -- just by the max... constants)
246
        -> Gen Node.Node
247
genNode min_multiplier max_multiplier = do
248
  let (base_mem, base_dsk, base_cpu) =
249
        case min_multiplier of
250
          Just mm -> (mm * Types.unitMem,
251
                      mm * Types.unitDsk,
252
                      mm * Types.unitCpu)
253
          Nothing -> (0, 0, 0)
254
      (top_mem, top_dsk, top_cpu)  =
255
        case max_multiplier of
256
          Just mm -> (mm * Types.unitMem,
257
                      mm * Types.unitDsk,
258
                      mm * Types.unitCpu)
259
          Nothing -> (maxMem, maxDsk, maxCpu)
260
  name  <- getFQDN
261
  mem_t <- choose (base_mem, top_mem)
262
  mem_f <- choose (base_mem, mem_t)
263
  mem_n <- choose (0, mem_t - mem_f)
264
  dsk_t <- choose (base_dsk, top_dsk)
265
  dsk_f <- choose (base_dsk, dsk_t)
266
  cpu_t <- choose (base_cpu, top_cpu)
267
  offl  <- arbitrary
268
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
269
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 0
270
      n' = Node.setPolicy nullIPolicy n
271
  return $ Node.buildPeers n' Container.empty
272

    
273
-- | Helper function to generate a sane node.
274
genOnlineNode :: Gen Node.Node
275
genOnlineNode = do
276
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
277
                              not (Node.failN1 n) &&
278
                              Node.availDisk n > 0 &&
279
                              Node.availMem n > 0 &&
280
                              Node.availCpu n > 0)
281

    
282
-- and a random node
283
instance Arbitrary Node.Node where
284
  arbitrary = genNode Nothing Nothing
285

    
286
-- replace disks
287
instance Arbitrary OpCodes.ReplaceDisksMode where
288
  arbitrary = elements [minBound..maxBound]
289

    
290
instance Arbitrary OpCodes.OpCode where
291
  arbitrary = do
292
    op_id <- elements [ "OP_TEST_DELAY"
293
                      , "OP_INSTANCE_REPLACE_DISKS"
294
                      , "OP_INSTANCE_FAILOVER"
295
                      , "OP_INSTANCE_MIGRATE"
296
                      ]
297
    case op_id of
298
      "OP_TEST_DELAY" ->
299
        liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
300
      "OP_INSTANCE_REPLACE_DISKS" ->
301
        liftM5 OpCodes.OpInstanceReplaceDisks arbitrary arbitrary
302
          arbitrary arbitrary arbitrary
303
      "OP_INSTANCE_FAILOVER" ->
304
        liftM3 OpCodes.OpInstanceFailover arbitrary arbitrary
305
          arbitrary
306
      "OP_INSTANCE_MIGRATE" ->
307
        liftM5 OpCodes.OpInstanceMigrate arbitrary arbitrary
308
          arbitrary arbitrary arbitrary
309
      _ -> fail "Wrong opcode"
310

    
311
instance Arbitrary Jobs.OpStatus where
312
  arbitrary = elements [minBound..maxBound]
313

    
314
instance Arbitrary Jobs.JobStatus where
315
  arbitrary = elements [minBound..maxBound]
316

    
317
newtype SmallRatio = SmallRatio Double deriving Show
318
instance Arbitrary SmallRatio where
319
  arbitrary = do
320
    v <- choose (0, 1)
321
    return $ SmallRatio v
322

    
323
instance Arbitrary Types.AllocPolicy where
324
  arbitrary = elements [minBound..maxBound]
325

    
326
instance Arbitrary Types.DiskTemplate where
327
  arbitrary = elements [minBound..maxBound]
328

    
329
instance Arbitrary Types.FailMode where
330
  arbitrary = elements [minBound..maxBound]
331

    
332
instance Arbitrary a => Arbitrary (Types.OpResult a) where
333
  arbitrary = arbitrary >>= \c ->
334
              if c
335
                then liftM Types.OpGood arbitrary
336
                else liftM Types.OpFail arbitrary
337

    
338
instance Arbitrary Types.ISpec where
339
  arbitrary = do
340
    mem <- arbitrary::Gen (NonNegative Int)
341
    dsk_c <- arbitrary::Gen (NonNegative Int)
342
    dsk_s <- arbitrary::Gen (NonNegative Int)
343
    cpu <- arbitrary::Gen (NonNegative Int)
344
    nic <- arbitrary::Gen (NonNegative Int)
345
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem
346
                       , Types.iSpecCpuCount   = fromIntegral cpu
347
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
348
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
349
                       , Types.iSpecNicCount   = fromIntegral nic
350
                       }
351

    
352
-- | Helper function to check whether a spec is LTE than another
353
iSpecSmaller :: Types.ISpec -> Types.ISpec -> Bool
354
iSpecSmaller imin imax =
355
  Types.iSpecMemorySize imin <= Types.iSpecMemorySize imax &&
356
  Types.iSpecCpuCount imin   <= Types.iSpecCpuCount imax &&
357
  Types.iSpecDiskSize imin   <= Types.iSpecDiskSize imax &&
358
  Types.iSpecDiskCount imin  <= Types.iSpecDiskCount imax &&
359
  Types.iSpecNicCount imin   <= Types.iSpecNicCount imax
360

    
361
instance Arbitrary Types.IPolicy where
362
  arbitrary = do
363
    imin <- arbitrary
364
    istd <- arbitrary `suchThat` (iSpecSmaller imin)
365
    imax <- arbitrary `suchThat` (iSpecSmaller istd)
366
    dts  <- arbitrary
367
    return Types.IPolicy { Types.iPolicyMinSpec = imin
368
                         , Types.iPolicyStdSpec = istd
369
                         , Types.iPolicyMaxSpec = imax
370
                         , Types.iPolicyDiskTemplates = dts
371
                         }
372

    
373
-- * Actual tests
374

    
375
-- ** Utils tests
376

    
377
-- | If the list is not just an empty element, and if the elements do
378
-- not contain commas, then join+split should be idempotent.
379
prop_Utils_commaJoinSplit =
380
  forAll (arbitrary `suchThat`
381
          (\l -> l /= [""] && all (notElem ',') l )) $ \lst ->
382
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
383

    
384
-- | Split and join should always be idempotent.
385
prop_Utils_commaSplitJoin s =
386
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
387

    
388
-- | fromObjWithDefault, we test using the Maybe monad and an integer
389
-- value.
390
prop_Utils_fromObjWithDefault def_value random_key =
391
  -- a missing key will be returned with the default
392
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
393
  -- a found key will be returned as is, not with default
394
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
395
       random_key (def_value+1) == Just def_value
396
    where _types = def_value :: Integer
397

    
398
-- | Test that functional if' behaves like the syntactic sugar if.
399
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
400
prop_Utils_if'if cnd a b =
401
  Utils.if' cnd a b ==? if cnd then a else b
402

    
403
-- | Test basic select functionality
404
prop_Utils_select :: Int      -- ^ Default result
405
                  -> [Int]    -- ^ List of False values
406
                  -> [Int]    -- ^ List of True values
407
                  -> Gen Prop -- ^ Test result
408
prop_Utils_select def lst1 lst2 =
409
  Utils.select def (flist ++ tlist) ==? expectedresult
410
    where expectedresult = Utils.if' (null lst2) def (head lst2)
411
          flist = zip (repeat False) lst1
412
          tlist = zip (repeat True)  lst2
413

    
414
-- | Test basic select functionality with undefined default
415
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
416
                         -> NonEmptyList Int -- ^ List of True values
417
                         -> Gen Prop         -- ^ Test result
418
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
419
  Utils.select undefined (flist ++ tlist) ==? head lst2
420
    where flist = zip (repeat False) lst1
421
          tlist = zip (repeat True)  lst2
422

    
423
-- | Test basic select functionality with undefined list values
424
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
425
                         -> NonEmptyList Int -- ^ List of True values
426
                         -> Gen Prop         -- ^ Test result
427
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
428
  Utils.select undefined cndlist ==? head lst2
429
    where flist = zip (repeat False) lst1
430
          tlist = zip (repeat True)  lst2
431
          cndlist = flist ++ tlist ++ [undefined]
432

    
433
prop_Utils_parseUnit (NonNegative n) =
434
  Utils.parseUnit (show n) == Types.Ok n &&
435
  Utils.parseUnit (show n ++ "m") == Types.Ok n &&
436
  (case Utils.parseUnit (show n ++ "M") of
437
     Types.Ok m -> if n > 0
438
                     then m < n  -- for positive values, X MB is < than X MiB
439
                     else m == 0 -- but for 0, 0 MB == 0 MiB
440
     Types.Bad _ -> False) &&
441
  Utils.parseUnit (show n ++ "g") == Types.Ok (n*1024) &&
442
  Utils.parseUnit (show n ++ "t") == Types.Ok (n*1048576) &&
443
  Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int)
444
    where _types = n::Int
445

    
446
-- | Test list for the Utils module.
447
testSuite "Utils"
448
            [ 'prop_Utils_commaJoinSplit
449
            , 'prop_Utils_commaSplitJoin
450
            , 'prop_Utils_fromObjWithDefault
451
            , 'prop_Utils_if'if
452
            , 'prop_Utils_select
453
            , 'prop_Utils_select_undefd
454
            , 'prop_Utils_select_undefv
455
            , 'prop_Utils_parseUnit
456
            ]
457

    
458
-- ** PeerMap tests
459

    
460
-- | Make sure add is idempotent.
461
prop_PeerMap_addIdempotent pmap key em =
462
  fn puniq ==? fn (fn puniq)
463
    where _types = (pmap::PeerMap.PeerMap,
464
                    key::PeerMap.Key, em::PeerMap.Elem)
465
          fn = PeerMap.add key em
466
          puniq = PeerMap.accumArray const pmap
467

    
468
-- | Make sure remove is idempotent.
469
prop_PeerMap_removeIdempotent pmap key =
470
  fn puniq ==? fn (fn puniq)
471
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
472
          fn = PeerMap.remove key
473
          puniq = PeerMap.accumArray const pmap
474

    
475
-- | Make sure a missing item returns 0.
476
prop_PeerMap_findMissing pmap key =
477
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
478
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
479
          puniq = PeerMap.accumArray const pmap
480

    
481
-- | Make sure an added item is found.
482
prop_PeerMap_addFind pmap key em =
483
  PeerMap.find key (PeerMap.add key em puniq) ==? em
484
    where _types = (pmap::PeerMap.PeerMap,
485
                    key::PeerMap.Key, em::PeerMap.Elem)
486
          puniq = PeerMap.accumArray const pmap
487

    
488
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
489
prop_PeerMap_maxElem pmap =
490
  PeerMap.maxElem puniq ==? if null puniq then 0
491
                              else (maximum . snd . unzip) puniq
492
    where _types = pmap::PeerMap.PeerMap
493
          puniq = PeerMap.accumArray const pmap
494

    
495
-- | List of tests for the PeerMap module.
496
testSuite "PeerMap"
497
            [ 'prop_PeerMap_addIdempotent
498
            , 'prop_PeerMap_removeIdempotent
499
            , 'prop_PeerMap_maxElem
500
            , 'prop_PeerMap_addFind
501
            , 'prop_PeerMap_findMissing
502
            ]
503

    
504
-- ** Container tests
505

    
506
-- we silence the following due to hlint bug fixed in later versions
507
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
508
prop_Container_addTwo cdata i1 i2 =
509
  fn i1 i2 cont == fn i2 i1 cont &&
510
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
511
    where _types = (cdata::[Int],
512
                    i1::Int, i2::Int)
513
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
514
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
515

    
516
prop_Container_nameOf node =
517
  let nl = makeSmallCluster node 1
518
      fnode = head (Container.elems nl)
519
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
520

    
521
-- | We test that in a cluster, given a random node, we can find it by
522
-- its name and alias, as long as all names and aliases are unique,
523
-- and that we fail to find a non-existing name.
524
prop_Container_findByName node othername =
525
  forAll (choose (1, 20)) $ \ cnt ->
526
  forAll (choose (0, cnt - 1)) $ \ fidx ->
527
  forAll (vector cnt) $ \ names ->
528
  (length . nub) (map fst names ++ map snd names) ==
529
  length names * 2 &&
530
  othername `notElem` (map fst names ++ map snd names) ==>
531
  let nl = makeSmallCluster node cnt
532
      nodes = Container.elems nl
533
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
534
                                             nn { Node.name = name,
535
                                                  Node.alias = alias }))
536
               $ zip names nodes
537
      nl' = Container.fromList nodes'
538
      target = snd (nodes' !! fidx)
539
  in Container.findByName nl' (Node.name target) == Just target &&
540
     Container.findByName nl' (Node.alias target) == Just target &&
541
     isNothing (Container.findByName nl' othername)
542

    
543
testSuite "Container"
544
            [ 'prop_Container_addTwo
545
            , 'prop_Container_nameOf
546
            , 'prop_Container_findByName
547
            ]
548

    
549
-- ** Instance tests
550

    
551
-- Simple instance tests, we only have setter/getters
552

    
553
prop_Instance_creat inst =
554
  Instance.name inst ==? Instance.alias inst
555

    
556
prop_Instance_setIdx inst idx =
557
  Instance.idx (Instance.setIdx inst idx) ==? idx
558
    where _types = (inst::Instance.Instance, idx::Types.Idx)
559

    
560
prop_Instance_setName inst name =
561
  Instance.name newinst == name &&
562
  Instance.alias newinst == name
563
    where _types = (inst::Instance.Instance, name::String)
564
          newinst = Instance.setName inst name
565

    
566
prop_Instance_setAlias inst name =
567
  Instance.name newinst == Instance.name inst &&
568
  Instance.alias newinst == name
569
    where _types = (inst::Instance.Instance, name::String)
570
          newinst = Instance.setAlias inst name
571

    
572
prop_Instance_setPri inst pdx =
573
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
574
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
575

    
576
prop_Instance_setSec inst sdx =
577
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
578
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
579

    
580
prop_Instance_setBoth inst pdx sdx =
581
  Instance.pNode si == pdx && Instance.sNode si == sdx
582
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
583
          si = Instance.setBoth inst pdx sdx
584

    
585
prop_Instance_shrinkMG inst =
586
  Instance.mem inst >= 2 * Types.unitMem ==>
587
    case Instance.shrinkByType inst Types.FailMem of
588
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
589
      _ -> False
590

    
591
prop_Instance_shrinkMF inst =
592
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
593
    let inst' = inst { Instance.mem = mem}
594
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
595

    
596
prop_Instance_shrinkCG inst =
597
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
598
    case Instance.shrinkByType inst Types.FailCPU of
599
      Types.Ok inst' ->
600
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
601
      _ -> False
602

    
603
prop_Instance_shrinkCF inst =
604
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
605
    let inst' = inst { Instance.vcpus = vcpus }
606
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
607

    
608
prop_Instance_shrinkDG inst =
609
  Instance.dsk inst >= 2 * Types.unitDsk ==>
610
    case Instance.shrinkByType inst Types.FailDisk of
611
      Types.Ok inst' ->
612
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
613
      _ -> False
614

    
615
prop_Instance_shrinkDF inst =
616
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
617
    let inst' = inst { Instance.dsk = dsk }
618
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
619

    
620
prop_Instance_setMovable inst m =
621
  Instance.movable inst' ==? m
622
    where inst' = Instance.setMovable inst m
623

    
624
testSuite "Instance"
625
            [ 'prop_Instance_creat
626
            , 'prop_Instance_setIdx
627
            , 'prop_Instance_setName
628
            , 'prop_Instance_setAlias
629
            , 'prop_Instance_setPri
630
            , 'prop_Instance_setSec
631
            , 'prop_Instance_setBoth
632
            , 'prop_Instance_shrinkMG
633
            , 'prop_Instance_shrinkMF
634
            , 'prop_Instance_shrinkCG
635
            , 'prop_Instance_shrinkCF
636
            , 'prop_Instance_shrinkDG
637
            , 'prop_Instance_shrinkDF
638
            , 'prop_Instance_setMovable
639
            ]
640

    
641
-- ** Text backend tests
642

    
643
-- Instance text loader tests
644

    
645
prop_Text_Load_Instance name mem dsk vcpus status
646
                        (NonEmpty pnode) snode
647
                        (NonNegative pdx) (NonNegative sdx) autobal dt =
648
  pnode /= snode && pdx /= sdx ==>
649
  let vcpus_s = show vcpus
650
      dsk_s = show dsk
651
      mem_s = show mem
652
      status_s = Types.instanceStatusToRaw status
653
      ndx = if null snode
654
              then [(pnode, pdx)]
655
              else [(pnode, pdx), (snode, sdx)]
656
      nl = Data.Map.fromList ndx
657
      tags = ""
658
      sbal = if autobal then "Y" else "N"
659
      sdt = Types.diskTemplateToRaw dt
660
      inst = Text.loadInst nl
661
             [name, mem_s, dsk_s, vcpus_s, status_s,
662
              sbal, pnode, snode, sdt, tags]
663
      fail1 = Text.loadInst nl
664
              [name, mem_s, dsk_s, vcpus_s, status_s,
665
               sbal, pnode, pnode, tags]
666
      _types = ( name::String, mem::Int, dsk::Int
667
               , vcpus::Int, status::Types.InstanceStatus
668
               , snode::String
669
               , autobal::Bool)
670
  in case inst of
671
       Types.Bad msg -> printTestCase ("Failed to load instance: " ++ msg)
672
                        False
673
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
674
                                        \ loading the instance" $
675
               Instance.name i == name &&
676
               Instance.vcpus i == vcpus &&
677
               Instance.mem i == mem &&
678
               Instance.pNode i == pdx &&
679
               Instance.sNode i == (if null snode
680
                                      then Node.noSecondary
681
                                      else sdx) &&
682
               Instance.autoBalance i == autobal &&
683
               Types.isBad fail1
684

    
685
prop_Text_Load_InstanceFail ktn fields =
686
  length fields /= 10 ==>
687
    case Text.loadInst nl fields of
688
      Types.Ok _ -> printTestCase "Managed to load instance from invalid\
689
                                  \ data" False
690
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
691
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
692
    where nl = Data.Map.fromList ktn
693

    
694
prop_Text_Load_Node name tm nm fm td fd tc fo =
695
  let conv v = if v < 0
696
                 then "?"
697
                 else show v
698
      tm_s = conv tm
699
      nm_s = conv nm
700
      fm_s = conv fm
701
      td_s = conv td
702
      fd_s = conv fd
703
      tc_s = conv tc
704
      fo_s = if fo
705
               then "Y"
706
               else "N"
707
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
708
      gid = Group.uuid defGroup
709
  in case Text.loadNode defGroupAssoc
710
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
711
       Nothing -> False
712
       Just (name', node) ->
713
         if fo || any_broken
714
           then Node.offline node
715
           else Node.name node == name' && name' == name &&
716
                Node.alias node == name &&
717
                Node.tMem node == fromIntegral tm &&
718
                Node.nMem node == nm &&
719
                Node.fMem node == fm &&
720
                Node.tDsk node == fromIntegral td &&
721
                Node.fDsk node == fd &&
722
                Node.tCpu node == fromIntegral tc
723

    
724
prop_Text_Load_NodeFail fields =
725
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
726

    
727
prop_Text_NodeLSIdempotent node =
728
  (Text.loadNode defGroupAssoc.
729
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==
730
  Just (Node.name n, n)
731
    -- override failN1 to what loadNode returns by default
732
    where n = node { Node.failN1 = True, Node.offline = False
733
                   , Node.iPolicy = Types.defIPolicy }
734

    
735
testSuite "Text"
736
            [ 'prop_Text_Load_Instance
737
            , 'prop_Text_Load_InstanceFail
738
            , 'prop_Text_Load_Node
739
            , 'prop_Text_Load_NodeFail
740
            , 'prop_Text_NodeLSIdempotent
741
            ]
742

    
743
-- ** Node tests
744

    
745
prop_Node_setAlias node name =
746
  Node.name newnode == Node.name node &&
747
  Node.alias newnode == name
748
    where _types = (node::Node.Node, name::String)
749
          newnode = Node.setAlias node name
750

    
751
prop_Node_setOffline node status =
752
  Node.offline newnode ==? status
753
    where newnode = Node.setOffline node status
754

    
755
prop_Node_setXmem node xm =
756
  Node.xMem newnode ==? xm
757
    where newnode = Node.setXmem node xm
758

    
759
prop_Node_setMcpu node mc =
760
  Node.mCpu newnode ==? mc
761
    where newnode = Node.setMcpu node mc
762

    
763
-- | Check that an instance add with too high memory or disk will be
764
-- rejected.
765
prop_Node_addPriFM node inst =
766
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
767
  not (Instance.instanceOffline inst) ==>
768
  case Node.addPri node inst'' of
769
    Types.OpFail Types.FailMem -> True
770
    _ -> False
771
  where _types = (node::Node.Node, inst::Instance.Instance)
772
        inst' = setInstanceSmallerThanNode node inst
773
        inst'' = inst' { Instance.mem = Instance.mem inst }
774

    
775
prop_Node_addPriFD node inst =
776
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
777
    case Node.addPri node inst'' of
778
      Types.OpFail Types.FailDisk -> True
779
      _ -> False
780
    where _types = (node::Node.Node, inst::Instance.Instance)
781
          inst' = setInstanceSmallerThanNode node inst
782
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
783

    
784
prop_Node_addPriFC node inst (Positive extra) =
785
  not (Node.failN1 node) && not (Instance.instanceOffline inst) ==>
786
      case Node.addPri node inst'' of
787
        Types.OpFail Types.FailCPU -> True
788
        _ -> False
789
    where _types = (node::Node.Node, inst::Instance.Instance)
790
          inst' = setInstanceSmallerThanNode node inst
791
          inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
792

    
793
-- | Check that an instance add with too high memory or disk will be
794
-- rejected.
795
prop_Node_addSec node inst pdx =
796
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
797
    not (Instance.instanceOffline inst)) ||
798
   Instance.dsk inst >= Node.fDsk node) &&
799
  not (Node.failN1 node) ==>
800
      isFailure (Node.addSec node inst pdx)
801
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
802

    
803
-- | Check that an offline instance with reasonable disk size can always
804
-- be added.
805
prop_Node_addPriOffline =
806
  forAll (arbitrary `suchThat` ((> 0) . Node.fMem)) $ \node ->
807
  forAll (arbitrary `suchThat`
808
          (\ x ->  (Instance.dsk x  < Node.fDsk node) &&
809
                   Instance.instanceOffline x)) $ \inst ->
810
  case Node.addPri node inst of
811
    Types.OpGood _ -> True
812
    _ -> False
813

    
814
prop_Node_addSecOffline pdx =
815
  forAll (arbitrary `suchThat` ((> 0) . Node.fMem)) $ \node ->
816
  forAll (arbitrary `suchThat`
817
          (\ x ->  (Instance.dsk x  < Node.fDsk node) &&
818
                   Instance.instanceOffline x)) $ \inst ->
819
  case Node.addSec node inst pdx of
820
    Types.OpGood _ -> True
821
    _ -> False
822

    
823
-- | Checks for memory reservation changes.
824
prop_Node_rMem inst =
825
  not (Instance.instanceOffline inst) ==>
826
  forAll (arbitrary `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
827
  -- ab = auto_balance, nb = non-auto_balance
828
  -- we use -1 as the primary node of the instance
829
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True }
830
      inst_ab = setInstanceSmallerThanNode node inst'
831
      inst_nb = inst_ab { Instance.autoBalance = False }
832
      -- now we have the two instances, identical except the
833
      -- autoBalance attribute
834
      orig_rmem = Node.rMem node
835
      inst_idx = Instance.idx inst_ab
836
      node_add_ab = Node.addSec node inst_ab (-1)
837
      node_add_nb = Node.addSec node inst_nb (-1)
838
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
839
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
840
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
841
       (Types.OpGood a_ab, Types.OpGood a_nb,
842
        Types.OpGood d_ab, Types.OpGood d_nb) ->
843
         printTestCase "Consistency checks failed" $
844
           Node.rMem a_ab >  orig_rmem &&
845
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
846
           Node.rMem a_nb == orig_rmem &&
847
           Node.rMem d_ab == orig_rmem &&
848
           Node.rMem d_nb == orig_rmem &&
849
           -- this is not related to rMem, but as good a place to
850
           -- test as any
851
           inst_idx `elem` Node.sList a_ab &&
852
           inst_idx `notElem` Node.sList d_ab
853
       x -> printTestCase ("Failed to add/remove instances: " ++ show x) False
854

    
855
-- | Check mdsk setting.
856
prop_Node_setMdsk node mx =
857
  Node.loDsk node' >= 0 &&
858
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
859
  Node.availDisk node' >= 0 &&
860
  Node.availDisk node' <= Node.fDsk node' &&
861
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
862
  Node.mDsk node' == mx'
863
    where _types = (node::Node.Node, mx::SmallRatio)
864
          node' = Node.setMdsk node mx'
865
          SmallRatio mx' = mx
866

    
867
-- Check tag maps
868
prop_Node_tagMaps_idempotent tags =
869
  Node.delTags (Node.addTags m tags) tags ==? m
870
    where m = Data.Map.empty
871

    
872
prop_Node_tagMaps_reject tags =
873
  not (null tags) ==>
874
  all (\t -> Node.rejectAddTags m [t]) tags
875
    where m = Node.addTags Data.Map.empty tags
876

    
877
prop_Node_showField node =
878
  forAll (elements Node.defaultFields) $ \ field ->
879
  fst (Node.showHeader field) /= Types.unknownField &&
880
  Node.showField node field /= Types.unknownField
881

    
882
prop_Node_computeGroups nodes =
883
  let ng = Node.computeGroups nodes
884
      onlyuuid = map fst ng
885
  in length nodes == sum (map (length . snd) ng) &&
886
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
887
     length (nub onlyuuid) == length onlyuuid &&
888
     (null nodes || not (null ng))
889

    
890
testSuite "Node"
891
            [ 'prop_Node_setAlias
892
            , 'prop_Node_setOffline
893
            , 'prop_Node_setMcpu
894
            , 'prop_Node_setXmem
895
            , 'prop_Node_addPriFM
896
            , 'prop_Node_addPriFD
897
            , 'prop_Node_addPriFC
898
            , 'prop_Node_addSec
899
            , 'prop_Node_addPriOffline
900
            , 'prop_Node_addSecOffline
901
            , 'prop_Node_rMem
902
            , 'prop_Node_setMdsk
903
            , 'prop_Node_tagMaps_idempotent
904
            , 'prop_Node_tagMaps_reject
905
            , 'prop_Node_showField
906
            , 'prop_Node_computeGroups
907
            ]
908

    
909
-- ** Cluster tests
910

    
911
-- | Check that the cluster score is close to zero for a homogeneous
912
-- cluster.
913
prop_Score_Zero node =
914
  forAll (choose (1, 1024)) $ \count ->
915
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
916
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
917
  let fn = Node.buildPeers node Container.empty
918
      nlst = replicate count fn
919
      score = Cluster.compCVNodes nlst
920
  -- we can't say == 0 here as the floating point errors accumulate;
921
  -- this should be much lower than the default score in CLI.hs
922
  in score <= 1e-12
923

    
924
-- | Check that cluster stats are sane.
925
prop_CStats_sane =
926
  forAll (choose (1, 1024)) $ \count ->
927
  forAll genOnlineNode $ \node ->
928
  let fn = Node.buildPeers node Container.empty
929
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
930
      nl = Container.fromList nlst
931
      cstats = Cluster.totalResources nl
932
  in Cluster.csAdsk cstats >= 0 &&
933
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
934

    
935
-- | Check that one instance is allocated correctly, without
936
-- rebalances needed.
937
prop_ClusterAlloc_sane inst =
938
  forAll (choose (5, 20)) $ \count ->
939
  forAll genOnlineNode $ \node ->
940
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
941
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
942
     Cluster.tryAlloc nl il inst' of
943
       Types.Bad _ -> False
944
       Types.Ok as ->
945
         case Cluster.asSolution as of
946
           Nothing -> False
947
           Just (xnl, xi, _, cv) ->
948
             let il' = Container.add (Instance.idx xi) xi il
949
                 tbl = Cluster.Table xnl il' cv []
950
             in not (canBalance tbl True True False)
951

    
952
-- | Checks that on a 2-5 node cluster, we can allocate a random
953
-- instance spec via tiered allocation (whatever the original instance
954
-- spec), on either one or two nodes.
955
prop_ClusterCanTieredAlloc inst =
956
  forAll (choose (2, 5)) $ \count ->
957
  forAll (choose (1, 2)) $ \rqnodes ->
958
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
959
  let nl = makeSmallCluster node count
960
      il = Container.empty
961
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
962
  in case allocnodes >>= \allocnodes' ->
963
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
964
       Types.Bad _ -> False
965
       Types.Ok (_, _, il', ixes, cstats) -> not (null ixes) &&
966
                                             IntMap.size il' == length ixes &&
967
                                             length ixes == length cstats
968

    
969
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
970
-- we can also evacuate it.
971
prop_ClusterAllocEvac inst =
972
  forAll (choose (4, 8)) $ \count ->
973
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
974
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
975
  in case Cluster.genAllocNodes defGroupList nl 2 True >>=
976
     Cluster.tryAlloc nl il inst' of
977
       Types.Bad _ -> False
978
       Types.Ok as ->
979
         case Cluster.asSolution as of
980
           Nothing -> False
981
           Just (xnl, xi, _, _) ->
982
             let sdx = Instance.sNode xi
983
                 il' = Container.add (Instance.idx xi) xi il
984
             in case IAlloc.processRelocate defGroupList xnl il'
985
                  (Instance.idx xi) 1 [sdx] of
986
                  Types.Ok _ -> True
987
                  _ -> False
988

    
989
-- | Check that allocating multiple instances on a cluster, then
990
-- adding an empty node, results in a valid rebalance.
991
prop_ClusterAllocBalance =
992
  forAll (genNode (Just 5) (Just 128)) $ \node ->
993
  forAll (choose (3, 5)) $ \count ->
994
  not (Node.offline node) && not (Node.failN1 node) ==>
995
  let nl = makeSmallCluster node count
996
      (hnode, nl') = IntMap.deleteFindMax nl
997
      il = Container.empty
998
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
999
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1000
  in case allocnodes >>= \allocnodes' ->
1001
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1002
       Types.Bad _ -> printTestCase "Failed to allocate" False
1003
       Types.Ok (_, _, _, [], _) -> printTestCase "Failed to allocate" False
1004
       Types.Ok (_, xnl, il', _, _) ->
1005
         let ynl = Container.add (Node.idx hnode) hnode xnl
1006
             cv = Cluster.compCV ynl
1007
             tbl = Cluster.Table ynl il' cv []
1008
         in printTestCase "Failed to rebalance" $
1009
            canBalance tbl True True False
1010

    
1011
-- | Checks consistency.
1012
prop_ClusterCheckConsistency node inst =
1013
  let nl = makeSmallCluster node 3
1014
      [node1, node2, node3] = Container.elems nl
1015
      node3' = node3 { Node.group = 1 }
1016
      nl' = Container.add (Node.idx node3') node3' nl
1017
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1018
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1019
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1020
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1021
  in null (ccheck [(0, inst1)]) &&
1022
     null (ccheck [(0, inst2)]) &&
1023
     (not . null $ ccheck [(0, inst3)])
1024

    
1025
-- | For now, we only test that we don't lose instances during the split.
1026
prop_ClusterSplitCluster node inst =
1027
  forAll (choose (0, 100)) $ \icnt ->
1028
  let nl = makeSmallCluster node 2
1029
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1030
                   (nl, Container.empty) [1..icnt]
1031
      gni = Cluster.splitCluster nl' il'
1032
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1033
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1034
                                 (Container.elems nl'')) gni
1035

    
1036
-- | Helper function to check if we can allocate an instance on a
1037
-- given node list.
1038
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1039
canAllocOn nl reqnodes inst =
1040
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1041
       Cluster.tryAlloc nl (Container.empty) inst of
1042
       Types.Bad _ -> False
1043
       Types.Ok as ->
1044
         case Cluster.asSolution as of
1045
           Nothing -> False
1046
           Just _ -> True
1047

    
1048
-- | Checks that allocation obeys minimum and maximum instance
1049
-- policies. The unittest generates a random node, duplicates it count
1050
-- times, and generates a random instance that can be allocated on
1051
-- this mini-cluster; it then checks that after applying a policy that
1052
-- the instance doesn't fits, the allocation fails.
1053
prop_ClusterAllocPolicy node =
1054
  -- rqn is the required nodes (1 or 2)
1055
  forAll (choose (1, 2)) $ \rqn ->
1056
  forAll (choose (5, 20)) $ \count ->
1057
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1058
         $ \inst ->
1059
  forAll (arbitrary `suchThat` (isFailure .
1060
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1061
  let node' = Node.setPolicy ipol node
1062
      nl = makeSmallCluster node' count
1063
  in not $ canAllocOn nl rqn inst
1064

    
1065
testSuite "Cluster"
1066
            [ 'prop_Score_Zero
1067
            , 'prop_CStats_sane
1068
            , 'prop_ClusterAlloc_sane
1069
            , 'prop_ClusterCanTieredAlloc
1070
            , 'prop_ClusterAllocEvac
1071
            , 'prop_ClusterAllocBalance
1072
            , 'prop_ClusterCheckConsistency
1073
            , 'prop_ClusterSplitCluster
1074
            , 'prop_ClusterAllocPolicy
1075
            ]
1076

    
1077
-- ** OpCodes tests
1078

    
1079
-- | Check that opcode serialization is idempotent.
1080
prop_OpCodes_serialization op =
1081
  case J.readJSON (J.showJSON op) of
1082
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1083
    J.Ok op' -> op ==? op'
1084
  where _types = op::OpCodes.OpCode
1085

    
1086
testSuite "OpCodes"
1087
            [ 'prop_OpCodes_serialization ]
1088

    
1089
-- ** Jobs tests
1090

    
1091
-- | Check that (queued) job\/opcode status serialization is idempotent.
1092
prop_OpStatus_serialization os =
1093
  case J.readJSON (J.showJSON os) of
1094
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1095
    J.Ok os' -> os ==? os'
1096
  where _types = os::Jobs.OpStatus
1097

    
1098
prop_JobStatus_serialization js =
1099
  case J.readJSON (J.showJSON js) of
1100
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1101
    J.Ok js' -> js ==? js'
1102
  where _types = js::Jobs.JobStatus
1103

    
1104
testSuite "Jobs"
1105
            [ 'prop_OpStatus_serialization
1106
            , 'prop_JobStatus_serialization
1107
            ]
1108

    
1109
-- ** Loader tests
1110

    
1111
prop_Loader_lookupNode ktn inst node =
1112
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1113
    where nl = Data.Map.fromList ktn
1114

    
1115
prop_Loader_lookupInstance kti inst =
1116
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1117
    where il = Data.Map.fromList kti
1118

    
1119
prop_Loader_assignIndices nodes =
1120
  Data.Map.size nassoc == length nodes &&
1121
  Container.size kt == length nodes &&
1122
  (if not (null nodes)
1123
   then maximum (IntMap.keys kt) == length nodes - 1
1124
   else True)
1125
    where (nassoc, kt) =
1126
            Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1127

    
1128
-- | Checks that the number of primary instances recorded on the nodes
1129
-- is zero.
1130
prop_Loader_mergeData ns =
1131
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1132
  in case Loader.mergeData [] [] [] []
1133
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1134
    Types.Bad _ -> False
1135
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1136
      let nodes = Container.elems nl
1137
          instances = Container.elems il
1138
      in (sum . map (length . Node.pList)) nodes == 0 &&
1139
         null instances
1140

    
1141
-- | Check that compareNameComponent on equal strings works.
1142
prop_Loader_compareNameComponent_equal :: String -> Bool
1143
prop_Loader_compareNameComponent_equal s =
1144
  Loader.compareNameComponent s s ==
1145
    Loader.LookupResult Loader.ExactMatch s
1146

    
1147
-- | Check that compareNameComponent on prefix strings works.
1148
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1149
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1150
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1151
    Loader.LookupResult Loader.PartialMatch s1
1152

    
1153
testSuite "Loader"
1154
            [ 'prop_Loader_lookupNode
1155
            , 'prop_Loader_lookupInstance
1156
            , 'prop_Loader_assignIndices
1157
            , 'prop_Loader_mergeData
1158
            , 'prop_Loader_compareNameComponent_equal
1159
            , 'prop_Loader_compareNameComponent_prefix
1160
            ]
1161

    
1162
-- ** Types tests
1163

    
1164
prop_Types_AllocPolicy_serialisation apol =
1165
  case J.readJSON (J.showJSON apol) of
1166
    J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1167
              p == apol
1168
    J.Error s -> printTestCase ("failed to deserialise: " ++ s) False
1169
      where _types = apol::Types.AllocPolicy
1170

    
1171
prop_Types_DiskTemplate_serialisation dt =
1172
  case J.readJSON (J.showJSON dt) of
1173
    J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1174
              p == dt
1175
    J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1176
                 False
1177
      where _types = dt::Types.DiskTemplate
1178

    
1179
prop_Types_opToResult op =
1180
  case op of
1181
    Types.OpFail _ -> Types.isBad r
1182
    Types.OpGood v -> case r of
1183
                        Types.Bad _ -> False
1184
                        Types.Ok v' -> v == v'
1185
  where r = Types.opToResult op
1186
        _types = op::Types.OpResult Int
1187

    
1188
prop_Types_eitherToResult ei =
1189
  case ei of
1190
    Left _ -> Types.isBad r
1191
    Right v -> case r of
1192
                 Types.Bad _ -> False
1193
                 Types.Ok v' -> v == v'
1194
    where r = Types.eitherToResult ei
1195
          _types = ei::Either String Int
1196

    
1197
testSuite "Types"
1198
            [ 'prop_Types_AllocPolicy_serialisation
1199
            , 'prop_Types_DiskTemplate_serialisation
1200
            , 'prop_Types_opToResult
1201
            , 'prop_Types_eitherToResult
1202
            ]