Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (66.4 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
  , testSimu
36
  , testOpCodes
37
  , testJobs
38
  , testCluster
39
  , testLoader
40
  , testTypes
41
  , testCLI
42
  , testJSON
43
  , testLUXI
44
  , testSsconf
45
  ) where
46

    
47
import Test.QuickCheck
48
import Text.Printf (printf)
49
import Data.List (findIndex, intercalate, nub, isPrefixOf)
50
import qualified Data.Set as Set
51
import Data.Maybe
52
import Control.Monad
53
import Control.Applicative
54
import qualified System.Console.GetOpt as GetOpt
55
import qualified Text.JSON as J
56
import qualified Data.Map
57
import qualified Data.IntMap as IntMap
58

    
59
import qualified Ganeti.BasicTypes as BasicTypes
60
import qualified Ganeti.OpCodes as OpCodes
61
import qualified Ganeti.Jobs as Jobs
62
import qualified Ganeti.Luxi as Luxi
63
import qualified Ganeti.Ssconf as Ssconf
64
import qualified Ganeti.HTools.CLI as CLI
65
import qualified Ganeti.HTools.Cluster as Cluster
66
import qualified Ganeti.HTools.Container as Container
67
import qualified Ganeti.HTools.ExtLoader
68
import qualified Ganeti.HTools.IAlloc as IAlloc
69
import qualified Ganeti.HTools.Instance as Instance
70
import qualified Ganeti.HTools.JSON as JSON
71
import qualified Ganeti.HTools.Loader as Loader
72
import qualified Ganeti.HTools.Luxi as HTools.Luxi
73
import qualified Ganeti.HTools.Node as Node
74
import qualified Ganeti.HTools.Group as Group
75
import qualified Ganeti.HTools.PeerMap as PeerMap
76
import qualified Ganeti.HTools.Rapi
77
import qualified Ganeti.HTools.Simu as Simu
78
import qualified Ganeti.HTools.Text as Text
79
import qualified Ganeti.HTools.Types as Types
80
import qualified Ganeti.HTools.Utils as Utils
81
import qualified Ganeti.HTools.Version
82
import qualified Ganeti.Constants as C
83

    
84
import qualified Ganeti.HTools.Program as Program
85
import qualified Ganeti.HTools.Program.Hail
86
import qualified Ganeti.HTools.Program.Hbal
87
import qualified Ganeti.HTools.Program.Hscan
88
import qualified Ganeti.HTools.Program.Hspace
89

    
90
import Ganeti.HTools.QCHelper (testSuite)
91

    
92
-- * Constants
93

    
94
-- | Maximum memory (1TiB, somewhat random value).
95
maxMem :: Int
96
maxMem = 1024 * 1024
97

    
98
-- | Maximum disk (8TiB, somewhat random value).
99
maxDsk :: Int
100
maxDsk = 1024 * 1024 * 8
101

    
102
-- | Max CPUs (1024, somewhat random value).
103
maxCpu :: Int
104
maxCpu = 1024
105

    
106
-- | Max vcpu ratio (random value).
107
maxVcpuRatio :: Double
108
maxVcpuRatio = 1024.0
109

    
110
-- | Max spindle ratio (random value).
111
maxSpindleRatio :: Double
112
maxSpindleRatio = 1024.0
113

    
114
-- | Max nodes, used just to limit arbitrary instances for smaller
115
-- opcode definitions (e.g. list of nodes in OpTestDelay).
116
maxNodes :: Int
117
maxNodes = 32
118

    
119
-- | Max opcodes or jobs in a submit job and submit many jobs.
120
maxOpCodes :: Int
121
maxOpCodes = 16
122

    
123
-- | All disk templates (used later)
124
allDiskTemplates :: [Types.DiskTemplate]
125
allDiskTemplates = [minBound..maxBound]
126

    
127
-- | Null iPolicy, and by null we mean very liberal.
128
nullIPolicy = Types.IPolicy
129
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
130
                                       , Types.iSpecCpuCount   = 0
131
                                       , Types.iSpecDiskSize   = 0
132
                                       , Types.iSpecDiskCount  = 0
133
                                       , Types.iSpecNicCount   = 0
134
                                       , Types.iSpecSpindleUse = 0
135
                                       }
136
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
137
                                       , Types.iSpecCpuCount   = maxBound
138
                                       , Types.iSpecDiskSize   = maxBound
139
                                       , Types.iSpecDiskCount  = C.maxDisks
140
                                       , Types.iSpecNicCount   = C.maxNics
141
                                       , Types.iSpecSpindleUse = maxBound
142
                                       }
143
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
144
                                       , Types.iSpecCpuCount   = Types.unitCpu
145
                                       , Types.iSpecDiskSize   = Types.unitDsk
146
                                       , Types.iSpecDiskCount  = 1
147
                                       , Types.iSpecNicCount   = 1
148
                                       , Types.iSpecSpindleUse = 1
149
                                       }
150
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
151
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
152
                                          -- enough to not impact us
153
  , Types.iPolicySpindleRatio = maxSpindleRatio
154
  }
155

    
156

    
157
defGroup :: Group.Group
158
defGroup = flip Group.setIdx 0 $
159
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
160
                  nullIPolicy []
161

    
162
defGroupList :: Group.List
163
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
164

    
165
defGroupAssoc :: Data.Map.Map String Types.Gdx
166
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
167

    
168
-- * Helper functions
169

    
170
-- | Simple checker for whether OpResult is fail or pass.
171
isFailure :: Types.OpResult a -> Bool
172
isFailure (Types.OpFail _) = True
173
isFailure _ = False
174

    
175
-- | Checks for equality with proper annotation.
176
(==?) :: (Show a, Eq a) => a -> a -> Property
177
(==?) x y = printTestCase
178
            ("Expected equality, but '" ++
179
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
180
infix 3 ==?
181

    
182
-- | Show a message and fail the test.
183
failTest :: String -> Property
184
failTest msg = printTestCase msg False
185

    
186
-- | Update an instance to be smaller than a node.
187
setInstanceSmallerThanNode node inst =
188
  inst { Instance.mem = Node.availMem node `div` 2
189
       , Instance.dsk = Node.availDisk node `div` 2
190
       , Instance.vcpus = Node.availCpu node `div` 2
191
       }
192

    
193
-- | Create an instance given its spec.
194
createInstance mem dsk vcpus =
195
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
196
    Types.DTDrbd8 1
197

    
198
-- | Create a small cluster by repeating a node spec.
199
makeSmallCluster :: Node.Node -> Int -> Node.List
200
makeSmallCluster node count =
201
  let origname = Node.name node
202
      origalias = Node.alias node
203
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
204
                                , Node.alias = origalias ++ "-" ++ show idx })
205
              [1..count]
206
      fn = flip Node.buildPeers Container.empty
207
      namelst = map (\n -> (Node.name n, fn n)) nodes
208
      (_, nlst) = Loader.assignIndices namelst
209
  in nlst
210

    
211
-- | Make a small cluster, both nodes and instances.
212
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
213
                      -> (Node.List, Instance.List, Instance.Instance)
214
makeSmallEmptyCluster node count inst =
215
  (makeSmallCluster node count, Container.empty,
216
   setInstanceSmallerThanNode node inst)
217

    
218
-- | Checks if a node is "big" enough.
219
isNodeBig :: Int -> Node.Node -> Bool
220
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
221
                      && Node.availMem node > size * Types.unitMem
222
                      && Node.availCpu node > size * Types.unitCpu
223

    
224
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
225
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
226

    
227
-- | Assigns a new fresh instance to a cluster; this is not
228
-- allocation, so no resource checks are done.
229
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
230
                  Types.Idx -> Types.Idx ->
231
                  (Node.List, Instance.List)
232
assignInstance nl il inst pdx sdx =
233
  let pnode = Container.find pdx nl
234
      snode = Container.find sdx nl
235
      maxiidx = if Container.null il
236
                  then 0
237
                  else fst (Container.findMax il) + 1
238
      inst' = inst { Instance.idx = maxiidx,
239
                     Instance.pNode = pdx, Instance.sNode = sdx }
240
      pnode' = Node.setPri pnode inst'
241
      snode' = Node.setSec snode inst'
242
      nl' = Container.addTwo pdx pnode' sdx snode' nl
243
      il' = Container.add maxiidx inst' il
244
  in (nl', il')
245

    
246
-- | Generates a list of a given size with non-duplicate elements.
247
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
248
genUniquesList cnt =
249
  foldM (\lst _ -> do
250
           newelem <- arbitrary `suchThat` (`notElem` lst)
251
           return (newelem:lst)) [] [1..cnt]
252

    
253
-- | Checks if an instance is mirrored.
254
isMirrored :: Instance.Instance -> Bool
255
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
256

    
257
-- | Returns the possible change node types for a disk template.
258
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
259
evacModeOptions Types.MirrorNone     = []
260
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
261
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
262

    
263
-- * Arbitrary instances
264

    
265
-- | Defines a DNS name.
266
newtype DNSChar = DNSChar { dnsGetChar::Char }
267

    
268
instance Arbitrary DNSChar where
269
  arbitrary = do
270
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
271
    return (DNSChar x)
272

    
273
-- | Generates a single name component.
274
getName :: Gen String
275
getName = do
276
  n <- choose (1, 64)
277
  dn <- vector n
278
  return (map dnsGetChar dn)
279

    
280
-- | Generates an entire FQDN.
281
getFQDN :: Gen String
282
getFQDN = do
283
  ncomps <- choose (1, 4)
284
  names <- vectorOf ncomps getName
285
  return $ intercalate "." names
286

    
287
-- | Combinator that generates a 'Maybe' using a sub-combinator.
288
getMaybe :: Gen a -> Gen (Maybe a)
289
getMaybe subgen = do
290
  bool <- arbitrary
291
  if bool
292
    then Just <$> subgen
293
    else return Nothing
294

    
295
-- | Generates a fields list. This uses the same character set as a
296
-- DNS name (just for simplicity).
297
getFields :: Gen [String]
298
getFields = do
299
  n <- choose (1, 32)
300
  vectorOf n getName
301

    
302
-- | Defines a tag type.
303
newtype TagChar = TagChar { tagGetChar :: Char }
304

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

    
310
instance Arbitrary TagChar where
311
  arbitrary = do
312
    c <- elements tagChar
313
    return (TagChar c)
314

    
315
-- | Generates a tag
316
genTag :: Gen [TagChar]
317
genTag = do
318
  -- the correct value would be C.maxTagLen, but that's way too
319
  -- verbose in unittests, and at the moment I don't see any possible
320
  -- bugs with longer tags and the way we use tags in htools
321
  n <- choose (1, 10)
322
  vector n
323

    
324
-- | Generates a list of tags (correctly upper bounded).
325
genTags :: Gen [String]
326
genTags = do
327
  -- the correct value would be C.maxTagsPerObj, but per the comment
328
  -- in genTag, we don't use tags enough in htools to warrant testing
329
  -- such big values
330
  n <- choose (0, 10::Int)
331
  tags <- mapM (const genTag) [1..n]
332
  return $ map (map tagGetChar) tags
333

    
334
instance Arbitrary Types.InstanceStatus where
335
    arbitrary = elements [minBound..maxBound]
336

    
337
-- | Generates a random instance with maximum disk/mem/cpu values.
338
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
339
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
340
  name <- getFQDN
341
  mem <- choose (0, lim_mem)
342
  dsk <- choose (0, lim_dsk)
343
  run_st <- arbitrary
344
  pn <- arbitrary
345
  sn <- arbitrary
346
  vcpus <- choose (0, lim_cpu)
347
  dt <- arbitrary
348
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
349

    
350
-- | Generates an instance smaller than a node.
351
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
352
genInstanceSmallerThanNode node =
353
  genInstanceSmallerThan (Node.availMem node `div` 2)
354
                         (Node.availDisk node `div` 2)
355
                         (Node.availCpu node `div` 2)
356

    
357
-- let's generate a random instance
358
instance Arbitrary Instance.Instance where
359
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
360

    
361
-- | Generas an arbitrary node based on sizing information.
362
genNode :: Maybe Int -- ^ Minimum node size in terms of units
363
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
364
                     -- just by the max... constants)
365
        -> Gen Node.Node
366
genNode min_multiplier max_multiplier = do
367
  let (base_mem, base_dsk, base_cpu) =
368
        case min_multiplier of
369
          Just mm -> (mm * Types.unitMem,
370
                      mm * Types.unitDsk,
371
                      mm * Types.unitCpu)
372
          Nothing -> (0, 0, 0)
373
      (top_mem, top_dsk, top_cpu)  =
374
        case max_multiplier of
375
          Just mm -> (mm * Types.unitMem,
376
                      mm * Types.unitDsk,
377
                      mm * Types.unitCpu)
378
          Nothing -> (maxMem, maxDsk, maxCpu)
379
  name  <- getFQDN
380
  mem_t <- choose (base_mem, top_mem)
381
  mem_f <- choose (base_mem, mem_t)
382
  mem_n <- choose (0, mem_t - mem_f)
383
  dsk_t <- choose (base_dsk, top_dsk)
384
  dsk_f <- choose (base_dsk, dsk_t)
385
  cpu_t <- choose (base_cpu, top_cpu)
386
  offl  <- arbitrary
387
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
388
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
389
      n' = Node.setPolicy nullIPolicy n
390
  return $ Node.buildPeers n' Container.empty
391

    
392
-- | Helper function to generate a sane node.
393
genOnlineNode :: Gen Node.Node
394
genOnlineNode = do
395
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
396
                              not (Node.failN1 n) &&
397
                              Node.availDisk n > 0 &&
398
                              Node.availMem n > 0 &&
399
                              Node.availCpu n > 0)
400

    
401
-- and a random node
402
instance Arbitrary Node.Node where
403
  arbitrary = genNode Nothing Nothing
404

    
405
-- replace disks
406
instance Arbitrary OpCodes.ReplaceDisksMode where
407
  arbitrary = elements [minBound..maxBound]
408

    
409
instance Arbitrary OpCodes.OpCode where
410
  arbitrary = do
411
    op_id <- elements [ "OP_TEST_DELAY"
412
                      , "OP_INSTANCE_REPLACE_DISKS"
413
                      , "OP_INSTANCE_FAILOVER"
414
                      , "OP_INSTANCE_MIGRATE"
415
                      ]
416
    case op_id of
417
      "OP_TEST_DELAY" ->
418
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
419
                 <*> resize maxNodes (listOf getFQDN)
420
      "OP_INSTANCE_REPLACE_DISKS" ->
421
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
422
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
423
      "OP_INSTANCE_FAILOVER" ->
424
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
425
          getMaybe getFQDN
426
      "OP_INSTANCE_MIGRATE" ->
427
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
428
          arbitrary <*> arbitrary <*> getMaybe getFQDN
429
      _ -> fail "Wrong opcode"
430

    
431
instance Arbitrary Jobs.OpStatus where
432
  arbitrary = elements [minBound..maxBound]
433

    
434
instance Arbitrary Jobs.JobStatus where
435
  arbitrary = elements [minBound..maxBound]
436

    
437
newtype SmallRatio = SmallRatio Double deriving Show
438
instance Arbitrary SmallRatio where
439
  arbitrary = do
440
    v <- choose (0, 1)
441
    return $ SmallRatio v
442

    
443
instance Arbitrary Types.AllocPolicy where
444
  arbitrary = elements [minBound..maxBound]
445

    
446
instance Arbitrary Types.DiskTemplate where
447
  arbitrary = elements [minBound..maxBound]
448

    
449
instance Arbitrary Types.FailMode where
450
  arbitrary = elements [minBound..maxBound]
451

    
452
instance Arbitrary Types.EvacMode where
453
  arbitrary = elements [minBound..maxBound]
454

    
455
instance Arbitrary a => Arbitrary (Types.OpResult a) where
456
  arbitrary = arbitrary >>= \c ->
457
              if c
458
                then Types.OpGood <$> arbitrary
459
                else Types.OpFail <$> arbitrary
460

    
461
instance Arbitrary Types.ISpec where
462
  arbitrary = do
463
    mem_s <- arbitrary::Gen (NonNegative Int)
464
    dsk_c <- arbitrary::Gen (NonNegative Int)
465
    dsk_s <- arbitrary::Gen (NonNegative Int)
466
    cpu_c <- arbitrary::Gen (NonNegative Int)
467
    nic_c <- arbitrary::Gen (NonNegative Int)
468
    su    <- arbitrary::Gen (NonNegative Int)
469
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
470
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
471
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
472
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
473
                       , Types.iSpecNicCount   = fromIntegral nic_c
474
                       , Types.iSpecSpindleUse = fromIntegral su
475
                       }
476

    
477
-- | Generates an ispec bigger than the given one.
478
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
479
genBiggerISpec imin = do
480
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
481
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
482
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
483
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
484
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
485
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
486
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
487
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
488
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
489
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
490
                     , Types.iSpecNicCount   = fromIntegral nic_c
491
                     , Types.iSpecSpindleUse = fromIntegral su
492
                     }
493

    
494
instance Arbitrary Types.IPolicy where
495
  arbitrary = do
496
    imin <- arbitrary
497
    istd <- genBiggerISpec imin
498
    imax <- genBiggerISpec istd
499
    num_tmpl <- choose (0, length allDiskTemplates)
500
    dts  <- genUniquesList num_tmpl
501
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
502
    spindle_ratio <- choose (1.0, maxSpindleRatio)
503
    return Types.IPolicy { Types.iPolicyMinSpec = imin
504
                         , Types.iPolicyStdSpec = istd
505
                         , Types.iPolicyMaxSpec = imax
506
                         , Types.iPolicyDiskTemplates = dts
507
                         , Types.iPolicyVcpuRatio = vcpu_ratio
508
                         , Types.iPolicySpindleRatio = spindle_ratio
509
                         }
510

    
511
-- * Actual tests
512

    
513
-- ** Utils tests
514

    
515
-- | Helper to generate a small string that doesn't contain commas.
516
genNonCommaString = do
517
  size <- choose (0, 20) -- arbitrary max size
518
  vectorOf size (arbitrary `suchThat` ((/=) ','))
519

    
520
-- | If the list is not just an empty element, and if the elements do
521
-- not contain commas, then join+split should be idempotent.
522
prop_Utils_commaJoinSplit =
523
  forAll (choose (0, 20)) $ \llen ->
524
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
525
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
526

    
527
-- | Split and join should always be idempotent.
528
prop_Utils_commaSplitJoin s =
529
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
530

    
531
-- | fromObjWithDefault, we test using the Maybe monad and an integer
532
-- value.
533
prop_Utils_fromObjWithDefault def_value random_key =
534
  -- a missing key will be returned with the default
535
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
536
  -- a found key will be returned as is, not with default
537
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
538
       random_key (def_value+1) == Just def_value
539
    where _types = def_value :: Integer
540

    
541
-- | Test that functional if' behaves like the syntactic sugar if.
542
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
543
prop_Utils_if'if cnd a b =
544
  Utils.if' cnd a b ==? if cnd then a else b
545

    
546
-- | Test basic select functionality
547
prop_Utils_select :: Int      -- ^ Default result
548
                  -> [Int]    -- ^ List of False values
549
                  -> [Int]    -- ^ List of True values
550
                  -> Gen Prop -- ^ Test result
551
prop_Utils_select def lst1 lst2 =
552
  Utils.select def (flist ++ tlist) ==? expectedresult
553
    where expectedresult = Utils.if' (null lst2) def (head lst2)
554
          flist = zip (repeat False) lst1
555
          tlist = zip (repeat True)  lst2
556

    
557
-- | Test basic select functionality with undefined default
558
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
559
                         -> NonEmptyList Int -- ^ List of True values
560
                         -> Gen Prop         -- ^ Test result
561
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
562
  Utils.select undefined (flist ++ tlist) ==? head lst2
563
    where flist = zip (repeat False) lst1
564
          tlist = zip (repeat True)  lst2
565

    
566
-- | Test basic select functionality with undefined list values
567
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
568
                         -> NonEmptyList Int -- ^ List of True values
569
                         -> Gen Prop         -- ^ Test result
570
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
571
  Utils.select undefined cndlist ==? head lst2
572
    where flist = zip (repeat False) lst1
573
          tlist = zip (repeat True)  lst2
574
          cndlist = flist ++ tlist ++ [undefined]
575

    
576
prop_Utils_parseUnit (NonNegative n) =
577
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
578
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
579
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
580
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
581
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
582
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
583
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
584
  printTestCase "Internal error/overflow?"
585
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
586
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
587
  where _types = (n::Int)
588
        n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
589
        n_gb = n_mb * 1000
590
        n_tb = n_gb * 1000
591

    
592
-- | Test list for the Utils module.
593
testSuite "Utils"
594
            [ 'prop_Utils_commaJoinSplit
595
            , 'prop_Utils_commaSplitJoin
596
            , 'prop_Utils_fromObjWithDefault
597
            , 'prop_Utils_if'if
598
            , 'prop_Utils_select
599
            , 'prop_Utils_select_undefd
600
            , 'prop_Utils_select_undefv
601
            , 'prop_Utils_parseUnit
602
            ]
603

    
604
-- ** PeerMap tests
605

    
606
-- | Make sure add is idempotent.
607
prop_PeerMap_addIdempotent pmap key em =
608
  fn puniq ==? fn (fn puniq)
609
    where _types = (pmap::PeerMap.PeerMap,
610
                    key::PeerMap.Key, em::PeerMap.Elem)
611
          fn = PeerMap.add key em
612
          puniq = PeerMap.accumArray const pmap
613

    
614
-- | Make sure remove is idempotent.
615
prop_PeerMap_removeIdempotent pmap key =
616
  fn puniq ==? fn (fn puniq)
617
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
618
          fn = PeerMap.remove key
619
          puniq = PeerMap.accumArray const pmap
620

    
621
-- | Make sure a missing item returns 0.
622
prop_PeerMap_findMissing pmap key =
623
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
624
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
625
          puniq = PeerMap.accumArray const pmap
626

    
627
-- | Make sure an added item is found.
628
prop_PeerMap_addFind pmap key em =
629
  PeerMap.find key (PeerMap.add key em puniq) ==? em
630
    where _types = (pmap::PeerMap.PeerMap,
631
                    key::PeerMap.Key, em::PeerMap.Elem)
632
          puniq = PeerMap.accumArray const pmap
633

    
634
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
635
prop_PeerMap_maxElem pmap =
636
  PeerMap.maxElem puniq ==? if null puniq then 0
637
                              else (maximum . snd . unzip) puniq
638
    where _types = pmap::PeerMap.PeerMap
639
          puniq = PeerMap.accumArray const pmap
640

    
641
-- | List of tests for the PeerMap module.
642
testSuite "PeerMap"
643
            [ 'prop_PeerMap_addIdempotent
644
            , 'prop_PeerMap_removeIdempotent
645
            , 'prop_PeerMap_maxElem
646
            , 'prop_PeerMap_addFind
647
            , 'prop_PeerMap_findMissing
648
            ]
649

    
650
-- ** Container tests
651

    
652
-- we silence the following due to hlint bug fixed in later versions
653
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
654
prop_Container_addTwo cdata i1 i2 =
655
  fn i1 i2 cont == fn i2 i1 cont &&
656
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
657
    where _types = (cdata::[Int],
658
                    i1::Int, i2::Int)
659
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
660
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
661

    
662
prop_Container_nameOf node =
663
  let nl = makeSmallCluster node 1
664
      fnode = head (Container.elems nl)
665
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
666

    
667
-- | We test that in a cluster, given a random node, we can find it by
668
-- its name and alias, as long as all names and aliases are unique,
669
-- and that we fail to find a non-existing name.
670
prop_Container_findByName =
671
  forAll (genNode (Just 1) Nothing) $ \node ->
672
  forAll (choose (1, 20)) $ \ cnt ->
673
  forAll (choose (0, cnt - 1)) $ \ fidx ->
674
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
675
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
676
  let names = zip (take cnt allnames) (drop cnt allnames)
677
      nl = makeSmallCluster node cnt
678
      nodes = Container.elems nl
679
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
680
                                             nn { Node.name = name,
681
                                                  Node.alias = alias }))
682
               $ zip names nodes
683
      nl' = Container.fromList nodes'
684
      target = snd (nodes' !! fidx)
685
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
686
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
687
     printTestCase "Found non-existing name"
688
       (isNothing (Container.findByName nl' othername))
689

    
690
testSuite "Container"
691
            [ 'prop_Container_addTwo
692
            , 'prop_Container_nameOf
693
            , 'prop_Container_findByName
694
            ]
695

    
696
-- ** Instance tests
697

    
698
-- Simple instance tests, we only have setter/getters
699

    
700
prop_Instance_creat inst =
701
  Instance.name inst ==? Instance.alias inst
702

    
703
prop_Instance_setIdx inst idx =
704
  Instance.idx (Instance.setIdx inst idx) ==? idx
705
    where _types = (inst::Instance.Instance, idx::Types.Idx)
706

    
707
prop_Instance_setName inst name =
708
  Instance.name newinst == name &&
709
  Instance.alias newinst == name
710
    where _types = (inst::Instance.Instance, name::String)
711
          newinst = Instance.setName inst name
712

    
713
prop_Instance_setAlias inst name =
714
  Instance.name newinst == Instance.name inst &&
715
  Instance.alias newinst == name
716
    where _types = (inst::Instance.Instance, name::String)
717
          newinst = Instance.setAlias inst name
718

    
719
prop_Instance_setPri inst pdx =
720
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
721
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
722

    
723
prop_Instance_setSec inst sdx =
724
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
725
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
726

    
727
prop_Instance_setBoth inst pdx sdx =
728
  Instance.pNode si == pdx && Instance.sNode si == sdx
729
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
730
          si = Instance.setBoth inst pdx sdx
731

    
732
prop_Instance_shrinkMG inst =
733
  Instance.mem inst >= 2 * Types.unitMem ==>
734
    case Instance.shrinkByType inst Types.FailMem of
735
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
736
      _ -> False
737

    
738
prop_Instance_shrinkMF inst =
739
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
740
    let inst' = inst { Instance.mem = mem}
741
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
742

    
743
prop_Instance_shrinkCG inst =
744
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
745
    case Instance.shrinkByType inst Types.FailCPU of
746
      Types.Ok inst' ->
747
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
748
      _ -> False
749

    
750
prop_Instance_shrinkCF inst =
751
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
752
    let inst' = inst { Instance.vcpus = vcpus }
753
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
754

    
755
prop_Instance_shrinkDG inst =
756
  Instance.dsk inst >= 2 * Types.unitDsk ==>
757
    case Instance.shrinkByType inst Types.FailDisk of
758
      Types.Ok inst' ->
759
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
760
      _ -> False
761

    
762
prop_Instance_shrinkDF inst =
763
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
764
    let inst' = inst { Instance.dsk = dsk }
765
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
766

    
767
prop_Instance_setMovable inst m =
768
  Instance.movable inst' ==? m
769
    where inst' = Instance.setMovable inst m
770

    
771
testSuite "Instance"
772
            [ 'prop_Instance_creat
773
            , 'prop_Instance_setIdx
774
            , 'prop_Instance_setName
775
            , 'prop_Instance_setAlias
776
            , 'prop_Instance_setPri
777
            , 'prop_Instance_setSec
778
            , 'prop_Instance_setBoth
779
            , 'prop_Instance_shrinkMG
780
            , 'prop_Instance_shrinkMF
781
            , 'prop_Instance_shrinkCG
782
            , 'prop_Instance_shrinkCF
783
            , 'prop_Instance_shrinkDG
784
            , 'prop_Instance_shrinkDF
785
            , 'prop_Instance_setMovable
786
            ]
787

    
788
-- ** Backends
789

    
790
-- *** Text backend tests
791

    
792
-- Instance text loader tests
793

    
794
prop_Text_Load_Instance name mem dsk vcpus status
795
                        (NonEmpty pnode) snode
796
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
797
  pnode /= snode && pdx /= sdx ==>
798
  let vcpus_s = show vcpus
799
      dsk_s = show dsk
800
      mem_s = show mem
801
      su_s = show su
802
      status_s = Types.instanceStatusToRaw status
803
      ndx = if null snode
804
              then [(pnode, pdx)]
805
              else [(pnode, pdx), (snode, sdx)]
806
      nl = Data.Map.fromList ndx
807
      tags = ""
808
      sbal = if autobal then "Y" else "N"
809
      sdt = Types.diskTemplateToRaw dt
810
      inst = Text.loadInst nl
811
             [name, mem_s, dsk_s, vcpus_s, status_s,
812
              sbal, pnode, snode, sdt, tags, su_s]
813
      fail1 = Text.loadInst nl
814
              [name, mem_s, dsk_s, vcpus_s, status_s,
815
               sbal, pnode, pnode, tags]
816
      _types = ( name::String, mem::Int, dsk::Int
817
               , vcpus::Int, status::Types.InstanceStatus
818
               , snode::String
819
               , autobal::Bool)
820
  in case inst of
821
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
822
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
823
                                        \ loading the instance" $
824
               Instance.name i == name &&
825
               Instance.vcpus i == vcpus &&
826
               Instance.mem i == mem &&
827
               Instance.pNode i == pdx &&
828
               Instance.sNode i == (if null snode
829
                                      then Node.noSecondary
830
                                      else sdx) &&
831
               Instance.autoBalance i == autobal &&
832
               Instance.spindleUse i == su &&
833
               Types.isBad fail1
834

    
835
prop_Text_Load_InstanceFail ktn fields =
836
  length fields /= 10 && length fields /= 11 ==>
837
    case Text.loadInst nl fields of
838
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
839
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
840
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
841
    where nl = Data.Map.fromList ktn
842

    
843
prop_Text_Load_Node name tm nm fm td fd tc fo =
844
  let conv v = if v < 0
845
                 then "?"
846
                 else show v
847
      tm_s = conv tm
848
      nm_s = conv nm
849
      fm_s = conv fm
850
      td_s = conv td
851
      fd_s = conv fd
852
      tc_s = conv tc
853
      fo_s = if fo
854
               then "Y"
855
               else "N"
856
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
857
      gid = Group.uuid defGroup
858
  in case Text.loadNode defGroupAssoc
859
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
860
       Nothing -> False
861
       Just (name', node) ->
862
         if fo || any_broken
863
           then Node.offline node
864
           else Node.name node == name' && name' == name &&
865
                Node.alias node == name &&
866
                Node.tMem node == fromIntegral tm &&
867
                Node.nMem node == nm &&
868
                Node.fMem node == fm &&
869
                Node.tDsk node == fromIntegral td &&
870
                Node.fDsk node == fd &&
871
                Node.tCpu node == fromIntegral tc
872

    
873
prop_Text_Load_NodeFail fields =
874
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
875

    
876
prop_Text_NodeLSIdempotent =
877
  forAll (genNode (Just 1) Nothing) $ \node ->
878
  -- override failN1 to what loadNode returns by default
879
  let n = Node.setPolicy Types.defIPolicy $
880
          node { Node.failN1 = True, Node.offline = False }
881
  in
882
    (Text.loadNode defGroupAssoc.
883
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
884
    Just (Node.name n, n)
885

    
886
prop_Text_ISpecIdempotent ispec =
887
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
888
       Text.serializeISpec $ ispec of
889
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
890
    Types.Ok ispec' -> ispec ==? ispec'
891

    
892
prop_Text_IPolicyIdempotent ipol =
893
  case Text.loadIPolicy . Utils.sepSplit '|' $
894
       Text.serializeIPolicy owner ipol of
895
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
896
    Types.Ok res -> (owner, ipol) ==? res
897
  where owner = "dummy"
898

    
899
-- | This property, while being in the text tests, does more than just
900
-- test end-to-end the serialisation and loading back workflow; it
901
-- also tests the Loader.mergeData and the actuall
902
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
903
-- allocations, not for the business logic). As such, it's a quite
904
-- complex and slow test, and that's the reason we restrict it to
905
-- small cluster sizes.
906
prop_Text_CreateSerialise =
907
  forAll genTags $ \ctags ->
908
  forAll (choose (1, 20)) $ \maxiter ->
909
  forAll (choose (2, 10)) $ \count ->
910
  forAll genOnlineNode $ \node ->
911
  forAll (genInstanceSmallerThanNode node) $ \inst ->
912
  let nl = makeSmallCluster node count
913
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
914
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
915
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
916
     of
917
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
918
       Types.Ok (_, _, _, [], _) -> printTestCase
919
                                    "Failed to allocate: no allocations" False
920
       Types.Ok (_, nl', il', _, _) ->
921
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
922
                     Types.defIPolicy
923
             saved = Text.serializeCluster cdata
924
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
925
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
926
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
927
                ctags ==? ctags2 .&&.
928
                Types.defIPolicy ==? cpol2 .&&.
929
                il' ==? il2 .&&.
930
                defGroupList ==? gl2 .&&.
931
                nl' ==? nl2
932

    
933
testSuite "Text"
934
            [ 'prop_Text_Load_Instance
935
            , 'prop_Text_Load_InstanceFail
936
            , 'prop_Text_Load_Node
937
            , 'prop_Text_Load_NodeFail
938
            , 'prop_Text_NodeLSIdempotent
939
            , 'prop_Text_ISpecIdempotent
940
            , 'prop_Text_IPolicyIdempotent
941
            , 'prop_Text_CreateSerialise
942
            ]
943

    
944
-- *** Simu backend
945

    
946
-- | Generates a tuple of specs for simulation.
947
genSimuSpec :: Gen (String, Int, Int, Int, Int)
948
genSimuSpec = do
949
  pol <- elements [C.allocPolicyPreferred,
950
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
951
                  "p", "a", "u"]
952
 -- should be reasonable (nodes/group), bigger values only complicate
953
 -- the display of failed tests, and we don't care (in this particular
954
 -- test) about big node groups
955
  nodes <- choose (0, 20)
956
  dsk <- choose (0, maxDsk)
957
  mem <- choose (0, maxMem)
958
  cpu <- choose (0, maxCpu)
959
  return (pol, nodes, dsk, mem, cpu)
960

    
961
-- | Checks that given a set of corrects specs, we can load them
962
-- successfully, and that at high-level the values look right.
963
prop_SimuLoad =
964
  forAll (choose (0, 10)) $ \ngroups ->
965
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
966
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
967
                                          p n d m c::String) specs
968
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
969
      mdc_in = concatMap (\(_, n, d, m, c) ->
970
                            replicate n (fromIntegral m, fromIntegral d,
971
                                         fromIntegral c,
972
                                         fromIntegral m, fromIntegral d)) specs
973
  in case Simu.parseData strspecs of
974
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
975
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
976
         let nodes = map snd $ IntMap.toAscList nl
977
             nidx = map Node.idx nodes
978
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
979
                                   Node.fMem n, Node.fDsk n)) nodes
980
         in
981
         Container.size gl ==? ngroups .&&.
982
         Container.size nl ==? totnodes .&&.
983
         Container.size il ==? 0 .&&.
984
         length tags ==? 0 .&&.
985
         ipol ==? Types.defIPolicy .&&.
986
         nidx ==? [1..totnodes] .&&.
987
         mdc_in ==? mdc_out .&&.
988
         map Group.iPolicy (Container.elems gl) ==?
989
             replicate ngroups Types.defIPolicy
990

    
991
testSuite "Simu"
992
            [ 'prop_SimuLoad
993
            ]
994

    
995
-- ** Node tests
996

    
997
prop_Node_setAlias node name =
998
  Node.name newnode == Node.name node &&
999
  Node.alias newnode == name
1000
    where _types = (node::Node.Node, name::String)
1001
          newnode = Node.setAlias node name
1002

    
1003
prop_Node_setOffline node status =
1004
  Node.offline newnode ==? status
1005
    where newnode = Node.setOffline node status
1006

    
1007
prop_Node_setXmem node xm =
1008
  Node.xMem newnode ==? xm
1009
    where newnode = Node.setXmem node xm
1010

    
1011
prop_Node_setMcpu node mc =
1012
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1013
    where newnode = Node.setMcpu node mc
1014

    
1015
-- | Check that an instance add with too high memory or disk will be
1016
-- rejected.
1017
prop_Node_addPriFM node inst =
1018
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1019
  not (Instance.isOffline inst) ==>
1020
  case Node.addPri node inst'' of
1021
    Types.OpFail Types.FailMem -> True
1022
    _ -> False
1023
  where _types = (node::Node.Node, inst::Instance.Instance)
1024
        inst' = setInstanceSmallerThanNode node inst
1025
        inst'' = inst' { Instance.mem = Instance.mem inst }
1026

    
1027
-- | Check that adding a primary instance with too much disk fails
1028
-- with type FailDisk.
1029
prop_Node_addPriFD node inst =
1030
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1031
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1032
  let inst' = setInstanceSmallerThanNode node inst
1033
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1034
                     , Instance.diskTemplate = dt }
1035
  in case Node.addPri node inst'' of
1036
       Types.OpFail Types.FailDisk -> True
1037
       _ -> False
1038

    
1039
-- | Check that adding a primary instance with too many VCPUs fails
1040
-- with type FailCPU.
1041
prop_Node_addPriFC =
1042
  forAll (choose (1, maxCpu)) $ \extra ->
1043
  forAll genOnlineNode $ \node ->
1044
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1045
  let inst' = setInstanceSmallerThanNode node inst
1046
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1047
  in case Node.addPri node inst'' of
1048
       Types.OpFail Types.FailCPU -> property True
1049
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1050

    
1051
-- | Check that an instance add with too high memory or disk will be
1052
-- rejected.
1053
prop_Node_addSec node inst pdx =
1054
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1055
    not (Instance.isOffline inst)) ||
1056
   Instance.dsk inst >= Node.fDsk node) &&
1057
  not (Node.failN1 node) ==>
1058
      isFailure (Node.addSec node inst pdx)
1059
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
1060

    
1061
-- | Check that an offline instance with reasonable disk size but
1062
-- extra mem/cpu can always be added.
1063
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1064
  forAll genOnlineNode $ \node ->
1065
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1066
  let inst' = inst { Instance.runSt = Types.AdminOffline
1067
                   , Instance.mem = Node.availMem node + extra_mem
1068
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1069
  in case Node.addPri node inst' of
1070
       Types.OpGood _ -> property True
1071
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1072

    
1073
-- | Check that an offline instance with reasonable disk size but
1074
-- extra mem/cpu can always be added.
1075
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1076
  forAll genOnlineNode $ \node ->
1077
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1078
  let inst' = inst { Instance.runSt = Types.AdminOffline
1079
                   , Instance.mem = Node.availMem node + extra_mem
1080
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1081
                   , Instance.diskTemplate = Types.DTDrbd8 }
1082
  in case Node.addSec node inst' pdx of
1083
       Types.OpGood _ -> property True
1084
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1085

    
1086
-- | Checks for memory reservation changes.
1087
prop_Node_rMem inst =
1088
  not (Instance.isOffline inst) ==>
1089
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1090
  -- ab = auto_balance, nb = non-auto_balance
1091
  -- we use -1 as the primary node of the instance
1092
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1093
                   , Instance.diskTemplate = Types.DTDrbd8 }
1094
      inst_ab = setInstanceSmallerThanNode node inst'
1095
      inst_nb = inst_ab { Instance.autoBalance = False }
1096
      -- now we have the two instances, identical except the
1097
      -- autoBalance attribute
1098
      orig_rmem = Node.rMem node
1099
      inst_idx = Instance.idx inst_ab
1100
      node_add_ab = Node.addSec node inst_ab (-1)
1101
      node_add_nb = Node.addSec node inst_nb (-1)
1102
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1103
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1104
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1105
       (Types.OpGood a_ab, Types.OpGood a_nb,
1106
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1107
         printTestCase "Consistency checks failed" $
1108
           Node.rMem a_ab >  orig_rmem &&
1109
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1110
           Node.rMem a_nb == orig_rmem &&
1111
           Node.rMem d_ab == orig_rmem &&
1112
           Node.rMem d_nb == orig_rmem &&
1113
           -- this is not related to rMem, but as good a place to
1114
           -- test as any
1115
           inst_idx `elem` Node.sList a_ab &&
1116
           inst_idx `notElem` Node.sList d_ab
1117
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1118

    
1119
-- | Check mdsk setting.
1120
prop_Node_setMdsk node mx =
1121
  Node.loDsk node' >= 0 &&
1122
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1123
  Node.availDisk node' >= 0 &&
1124
  Node.availDisk node' <= Node.fDsk node' &&
1125
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1126
  Node.mDsk node' == mx'
1127
    where _types = (node::Node.Node, mx::SmallRatio)
1128
          node' = Node.setMdsk node mx'
1129
          SmallRatio mx' = mx
1130

    
1131
-- Check tag maps
1132
prop_Node_tagMaps_idempotent =
1133
  forAll genTags $ \tags ->
1134
  Node.delTags (Node.addTags m tags) tags ==? m
1135
    where m = Data.Map.empty
1136

    
1137
prop_Node_tagMaps_reject =
1138
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1139
  let m = Node.addTags Data.Map.empty tags
1140
  in all (\t -> Node.rejectAddTags m [t]) tags
1141

    
1142
prop_Node_showField node =
1143
  forAll (elements Node.defaultFields) $ \ field ->
1144
  fst (Node.showHeader field) /= Types.unknownField &&
1145
  Node.showField node field /= Types.unknownField
1146

    
1147
prop_Node_computeGroups nodes =
1148
  let ng = Node.computeGroups nodes
1149
      onlyuuid = map fst ng
1150
  in length nodes == sum (map (length . snd) ng) &&
1151
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1152
     length (nub onlyuuid) == length onlyuuid &&
1153
     (null nodes || not (null ng))
1154

    
1155
-- Check idempotence of add/remove operations
1156
prop_Node_addPri_idempotent =
1157
  forAll genOnlineNode $ \node ->
1158
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1159
  case Node.addPri node inst of
1160
    Types.OpGood node' -> Node.removePri node' inst ==? node
1161
    _ -> failTest "Can't add instance"
1162

    
1163
prop_Node_addSec_idempotent =
1164
  forAll genOnlineNode $ \node ->
1165
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1166
  let pdx = Node.idx node + 1
1167
      inst' = Instance.setPri inst pdx
1168
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1169
  in case Node.addSec node inst'' pdx of
1170
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1171
       _ -> failTest "Can't add instance"
1172

    
1173
testSuite "Node"
1174
            [ 'prop_Node_setAlias
1175
            , 'prop_Node_setOffline
1176
            , 'prop_Node_setMcpu
1177
            , 'prop_Node_setXmem
1178
            , 'prop_Node_addPriFM
1179
            , 'prop_Node_addPriFD
1180
            , 'prop_Node_addPriFC
1181
            , 'prop_Node_addSec
1182
            , 'prop_Node_addOfflinePri
1183
            , 'prop_Node_addOfflineSec
1184
            , 'prop_Node_rMem
1185
            , 'prop_Node_setMdsk
1186
            , 'prop_Node_tagMaps_idempotent
1187
            , 'prop_Node_tagMaps_reject
1188
            , 'prop_Node_showField
1189
            , 'prop_Node_computeGroups
1190
            , 'prop_Node_addPri_idempotent
1191
            , 'prop_Node_addSec_idempotent
1192
            ]
1193

    
1194
-- ** Cluster tests
1195

    
1196
-- | Check that the cluster score is close to zero for a homogeneous
1197
-- cluster.
1198
prop_Score_Zero node =
1199
  forAll (choose (1, 1024)) $ \count ->
1200
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1201
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1202
  let fn = Node.buildPeers node Container.empty
1203
      nlst = replicate count fn
1204
      score = Cluster.compCVNodes nlst
1205
  -- we can't say == 0 here as the floating point errors accumulate;
1206
  -- this should be much lower than the default score in CLI.hs
1207
  in score <= 1e-12
1208

    
1209
-- | Check that cluster stats are sane.
1210
prop_CStats_sane =
1211
  forAll (choose (1, 1024)) $ \count ->
1212
  forAll genOnlineNode $ \node ->
1213
  let fn = Node.buildPeers node Container.empty
1214
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1215
      nl = Container.fromList nlst
1216
      cstats = Cluster.totalResources nl
1217
  in Cluster.csAdsk cstats >= 0 &&
1218
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1219

    
1220
-- | Check that one instance is allocated correctly, without
1221
-- rebalances needed.
1222
prop_ClusterAlloc_sane inst =
1223
  forAll (choose (5, 20)) $ \count ->
1224
  forAll genOnlineNode $ \node ->
1225
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1226
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1227
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1228
     Cluster.tryAlloc nl il inst' of
1229
       Types.Bad _ -> False
1230
       Types.Ok as ->
1231
         case Cluster.asSolution as of
1232
           Nothing -> False
1233
           Just (xnl, xi, _, cv) ->
1234
             let il' = Container.add (Instance.idx xi) xi il
1235
                 tbl = Cluster.Table xnl il' cv []
1236
             in not (canBalance tbl True True False)
1237

    
1238
-- | Checks that on a 2-5 node cluster, we can allocate a random
1239
-- instance spec via tiered allocation (whatever the original instance
1240
-- spec), on either one or two nodes. Furthermore, we test that
1241
-- computed allocation statistics are correct.
1242
prop_ClusterCanTieredAlloc inst =
1243
  forAll (choose (2, 5)) $ \count ->
1244
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1245
  let nl = makeSmallCluster node count
1246
      il = Container.empty
1247
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1248
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1249
  in case allocnodes >>= \allocnodes' ->
1250
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1251
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1252
       Types.Ok (_, nl', il', ixes, cstats) ->
1253
         let (ai_alloc, ai_pool, ai_unav) =
1254
               Cluster.computeAllocationDelta
1255
                (Cluster.totalResources nl)
1256
                (Cluster.totalResources nl')
1257
             all_nodes = Container.elems nl
1258
         in property (not (null ixes)) .&&.
1259
            IntMap.size il' ==? length ixes .&&.
1260
            length ixes ==? length cstats .&&.
1261
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1262
              sum (map Node.hiCpu all_nodes) .&&.
1263
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1264
              sum (map Node.tCpu all_nodes) .&&.
1265
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1266
              truncate (sum (map Node.tMem all_nodes)) .&&.
1267
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1268
              truncate (sum (map Node.tDsk all_nodes))
1269

    
1270
-- | Helper function to create a cluster with the given range of nodes
1271
-- and allocate an instance on it.
1272
genClusterAlloc count node inst =
1273
  let nl = makeSmallCluster node count
1274
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1275
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1276
     Cluster.tryAlloc nl Container.empty inst of
1277
       Types.Bad _ -> Types.Bad "Can't allocate"
1278
       Types.Ok as ->
1279
         case Cluster.asSolution as of
1280
           Nothing -> Types.Bad "Empty solution?"
1281
           Just (xnl, xi, _, _) ->
1282
             let xil = Container.add (Instance.idx xi) xi Container.empty
1283
             in Types.Ok (xnl, xil, xi)
1284

    
1285
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1286
-- we can also relocate it.
1287
prop_ClusterAllocRelocate =
1288
  forAll (choose (4, 8)) $ \count ->
1289
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1290
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1291
  case genClusterAlloc count node inst of
1292
    Types.Bad msg -> failTest msg
1293
    Types.Ok (nl, il, inst') ->
1294
      case IAlloc.processRelocate defGroupList nl il
1295
             (Instance.idx inst) 1
1296
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1297
                 then Instance.sNode
1298
                 else Instance.pNode) inst'] of
1299
        Types.Ok _ -> property True
1300
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1301

    
1302
-- | Helper property checker for the result of a nodeEvac or
1303
-- changeGroup operation.
1304
check_EvacMode grp inst result =
1305
  case result of
1306
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1307
    Types.Ok (_, _, es) ->
1308
      let moved = Cluster.esMoved es
1309
          failed = Cluster.esFailed es
1310
          opcodes = not . null $ Cluster.esOpCodes es
1311
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1312
         failmsg "'opcodes' is null" opcodes .&&.
1313
         case moved of
1314
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1315
                               .&&.
1316
                               failmsg "wrong target group"
1317
                                         (gdx == Group.idx grp)
1318
           v -> failmsg  ("invalid solution: " ++ show v) False
1319
  where failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1320
        idx = Instance.idx inst
1321

    
1322
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1323
-- we can also node-evacuate it.
1324
prop_ClusterAllocEvacuate =
1325
  forAll (choose (4, 8)) $ \count ->
1326
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1327
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1328
  case genClusterAlloc count node inst of
1329
    Types.Bad msg -> failTest msg
1330
    Types.Ok (nl, il, inst') ->
1331
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1332
                              Cluster.tryNodeEvac defGroupList nl il mode
1333
                                [Instance.idx inst']) .
1334
                              evacModeOptions .
1335
                              Instance.mirrorType $ inst'
1336

    
1337
-- | Checks that on a 4-8 node cluster with two node groups, once we
1338
-- allocate an instance on the first node group, we can also change
1339
-- its group.
1340
prop_ClusterAllocChangeGroup =
1341
  forAll (choose (4, 8)) $ \count ->
1342
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1343
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1344
  case genClusterAlloc count node inst of
1345
    Types.Bad msg -> failTest msg
1346
    Types.Ok (nl, il, inst') ->
1347
      -- we need to add a second node group and nodes to the cluster
1348
      let nl2 = Container.elems $ makeSmallCluster node count
1349
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1350
          maxndx = maximum . map Node.idx $ nl2
1351
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1352
                             , Node.idx = Node.idx n + maxndx }) nl2
1353
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1354
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1355
          nl' = IntMap.union nl nl4
1356
      in check_EvacMode grp2 inst' $
1357
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1358

    
1359
-- | Check that allocating multiple instances on a cluster, then
1360
-- adding an empty node, results in a valid rebalance.
1361
prop_ClusterAllocBalance =
1362
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1363
  forAll (choose (3, 5)) $ \count ->
1364
  not (Node.offline node) && not (Node.failN1 node) ==>
1365
  let nl = makeSmallCluster node count
1366
      (hnode, nl') = IntMap.deleteFindMax nl
1367
      il = Container.empty
1368
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1369
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1370
  in case allocnodes >>= \allocnodes' ->
1371
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1372
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1373
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1374
       Types.Ok (_, xnl, il', _, _) ->
1375
         let ynl = Container.add (Node.idx hnode) hnode xnl
1376
             cv = Cluster.compCV ynl
1377
             tbl = Cluster.Table ynl il' cv []
1378
         in printTestCase "Failed to rebalance" $
1379
            canBalance tbl True True False
1380

    
1381
-- | Checks consistency.
1382
prop_ClusterCheckConsistency node inst =
1383
  let nl = makeSmallCluster node 3
1384
      [node1, node2, node3] = Container.elems nl
1385
      node3' = node3 { Node.group = 1 }
1386
      nl' = Container.add (Node.idx node3') node3' nl
1387
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1388
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1389
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1390
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1391
  in null (ccheck [(0, inst1)]) &&
1392
     null (ccheck [(0, inst2)]) &&
1393
     (not . null $ ccheck [(0, inst3)])
1394

    
1395
-- | For now, we only test that we don't lose instances during the split.
1396
prop_ClusterSplitCluster node inst =
1397
  forAll (choose (0, 100)) $ \icnt ->
1398
  let nl = makeSmallCluster node 2
1399
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1400
                   (nl, Container.empty) [1..icnt]
1401
      gni = Cluster.splitCluster nl' il'
1402
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1403
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1404
                                 (Container.elems nl'')) gni
1405

    
1406
-- | Helper function to check if we can allocate an instance on a
1407
-- given node list.
1408
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1409
canAllocOn nl reqnodes inst =
1410
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1411
       Cluster.tryAlloc nl (Container.empty) inst of
1412
       Types.Bad _ -> False
1413
       Types.Ok as ->
1414
         case Cluster.asSolution as of
1415
           Nothing -> False
1416
           Just _ -> True
1417

    
1418
-- | Checks that allocation obeys minimum and maximum instance
1419
-- policies. The unittest generates a random node, duplicates it count
1420
-- times, and generates a random instance that can be allocated on
1421
-- this mini-cluster; it then checks that after applying a policy that
1422
-- the instance doesn't fits, the allocation fails.
1423
prop_ClusterAllocPolicy node =
1424
  -- rqn is the required nodes (1 or 2)
1425
  forAll (choose (1, 2)) $ \rqn ->
1426
  forAll (choose (5, 20)) $ \count ->
1427
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1428
         $ \inst ->
1429
  forAll (arbitrary `suchThat` (isFailure .
1430
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1431
  let node' = Node.setPolicy ipol node
1432
      nl = makeSmallCluster node' count
1433
  in not $ canAllocOn nl rqn inst
1434

    
1435
testSuite "Cluster"
1436
            [ 'prop_Score_Zero
1437
            , 'prop_CStats_sane
1438
            , 'prop_ClusterAlloc_sane
1439
            , 'prop_ClusterCanTieredAlloc
1440
            , 'prop_ClusterAllocRelocate
1441
            , 'prop_ClusterAllocEvacuate
1442
            , 'prop_ClusterAllocChangeGroup
1443
            , 'prop_ClusterAllocBalance
1444
            , 'prop_ClusterCheckConsistency
1445
            , 'prop_ClusterSplitCluster
1446
            , 'prop_ClusterAllocPolicy
1447
            ]
1448

    
1449
-- ** OpCodes tests
1450

    
1451
-- | Check that opcode serialization is idempotent.
1452
prop_OpCodes_serialization op =
1453
  case J.readJSON (J.showJSON op) of
1454
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1455
    J.Ok op' -> op ==? op'
1456
  where _types = op::OpCodes.OpCode
1457

    
1458
testSuite "OpCodes"
1459
            [ 'prop_OpCodes_serialization ]
1460

    
1461
-- ** Jobs tests
1462

    
1463
-- | Check that (queued) job\/opcode status serialization is idempotent.
1464
prop_OpStatus_serialization os =
1465
  case J.readJSON (J.showJSON os) of
1466
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1467
    J.Ok os' -> os ==? os'
1468
  where _types = os::Jobs.OpStatus
1469

    
1470
prop_JobStatus_serialization js =
1471
  case J.readJSON (J.showJSON js) of
1472
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1473
    J.Ok js' -> js ==? js'
1474
  where _types = js::Jobs.JobStatus
1475

    
1476
testSuite "Jobs"
1477
            [ 'prop_OpStatus_serialization
1478
            , 'prop_JobStatus_serialization
1479
            ]
1480

    
1481
-- ** Loader tests
1482

    
1483
prop_Loader_lookupNode ktn inst node =
1484
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1485
    where nl = Data.Map.fromList ktn
1486

    
1487
prop_Loader_lookupInstance kti inst =
1488
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1489
    where il = Data.Map.fromList kti
1490

    
1491
prop_Loader_assignIndices =
1492
  -- generate nodes with unique names
1493
  forAll (arbitrary `suchThat`
1494
          (\nodes ->
1495
             let names = map Node.name nodes
1496
             in length names == length (nub names))) $ \nodes ->
1497
  let (nassoc, kt) =
1498
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1499
  in Data.Map.size nassoc == length nodes &&
1500
     Container.size kt == length nodes &&
1501
     if not (null nodes)
1502
       then maximum (IntMap.keys kt) == length nodes - 1
1503
       else True
1504

    
1505
-- | Checks that the number of primary instances recorded on the nodes
1506
-- is zero.
1507
prop_Loader_mergeData ns =
1508
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1509
  in case Loader.mergeData [] [] [] []
1510
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1511
    Types.Bad _ -> False
1512
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1513
      let nodes = Container.elems nl
1514
          instances = Container.elems il
1515
      in (sum . map (length . Node.pList)) nodes == 0 &&
1516
         null instances
1517

    
1518
-- | Check that compareNameComponent on equal strings works.
1519
prop_Loader_compareNameComponent_equal :: String -> Bool
1520
prop_Loader_compareNameComponent_equal s =
1521
  BasicTypes.compareNameComponent s s ==
1522
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1523

    
1524
-- | Check that compareNameComponent on prefix strings works.
1525
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1526
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1527
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1528
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1529

    
1530
testSuite "Loader"
1531
            [ 'prop_Loader_lookupNode
1532
            , 'prop_Loader_lookupInstance
1533
            , 'prop_Loader_assignIndices
1534
            , 'prop_Loader_mergeData
1535
            , 'prop_Loader_compareNameComponent_equal
1536
            , 'prop_Loader_compareNameComponent_prefix
1537
            ]
1538

    
1539
-- ** Types tests
1540

    
1541
prop_Types_AllocPolicy_serialisation apol =
1542
  case J.readJSON (J.showJSON apol) of
1543
    J.Ok p -> p ==? apol
1544
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1545
      where _types = apol::Types.AllocPolicy
1546

    
1547
prop_Types_DiskTemplate_serialisation dt =
1548
  case J.readJSON (J.showJSON dt) of
1549
    J.Ok p -> p ==? dt
1550
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1551
      where _types = dt::Types.DiskTemplate
1552

    
1553
prop_Types_ISpec_serialisation ispec =
1554
  case J.readJSON (J.showJSON ispec) of
1555
    J.Ok p -> p ==? ispec
1556
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1557
      where _types = ispec::Types.ISpec
1558

    
1559
prop_Types_IPolicy_serialisation ipol =
1560
  case J.readJSON (J.showJSON ipol) of
1561
    J.Ok p -> p ==? ipol
1562
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1563
      where _types = ipol::Types.IPolicy
1564

    
1565
prop_Types_EvacMode_serialisation em =
1566
  case J.readJSON (J.showJSON em) of
1567
    J.Ok p -> p ==? em
1568
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1569
      where _types = em::Types.EvacMode
1570

    
1571
prop_Types_opToResult op =
1572
  case op of
1573
    Types.OpFail _ -> Types.isBad r
1574
    Types.OpGood v -> case r of
1575
                        Types.Bad _ -> False
1576
                        Types.Ok v' -> v == v'
1577
  where r = Types.opToResult op
1578
        _types = op::Types.OpResult Int
1579

    
1580
prop_Types_eitherToResult ei =
1581
  case ei of
1582
    Left _ -> Types.isBad r
1583
    Right v -> case r of
1584
                 Types.Bad _ -> False
1585
                 Types.Ok v' -> v == v'
1586
    where r = Types.eitherToResult ei
1587
          _types = ei::Either String Int
1588

    
1589
testSuite "Types"
1590
            [ 'prop_Types_AllocPolicy_serialisation
1591
            , 'prop_Types_DiskTemplate_serialisation
1592
            , 'prop_Types_ISpec_serialisation
1593
            , 'prop_Types_IPolicy_serialisation
1594
            , 'prop_Types_EvacMode_serialisation
1595
            , 'prop_Types_opToResult
1596
            , 'prop_Types_eitherToResult
1597
            ]
1598

    
1599
-- ** CLI tests
1600

    
1601
-- | Test correct parsing.
1602
prop_CLI_parseISpec descr dsk mem cpu =
1603
  let str = printf "%d,%d,%d" dsk mem cpu
1604
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1605

    
1606
-- | Test parsing failure due to wrong section count.
1607
prop_CLI_parseISpecFail descr =
1608
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1609
  forAll (replicateM nelems arbitrary) $ \values ->
1610
  let str = intercalate "," $ map show (values::[Int])
1611
  in case CLI.parseISpecString descr str of
1612
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1613
       _ -> property True
1614

    
1615
-- | Test parseYesNo.
1616
prop_CLI_parseYesNo def testval val =
1617
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1618
  if testval
1619
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1620
    else let result = CLI.parseYesNo def (Just actual_val)
1621
         in if actual_val `elem` ["yes", "no"]
1622
              then result ==? Types.Ok (actual_val == "yes")
1623
              else property $ Types.isBad result
1624

    
1625
-- | Helper to check for correct parsing of string arg.
1626
checkStringArg val (opt, fn) =
1627
  let GetOpt.Option _ longs _ _ = opt
1628
  in case longs of
1629
       [] -> failTest "no long options?"
1630
       cmdarg:_ ->
1631
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1632
           Left e -> failTest $ "Failed to parse option: " ++ show e
1633
           Right (options, _) -> fn options ==? Just val
1634

    
1635
-- | Test a few string arguments.
1636
prop_CLI_StringArg argument =
1637
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1638
             , (CLI.oDynuFile,      CLI.optDynuFile)
1639
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1640
             , (CLI.oReplay,        CLI.optReplay)
1641
             , (CLI.oPrintCommands, CLI.optShowCmds)
1642
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1643
             ]
1644
  in conjoin $ map (checkStringArg argument) args
1645

    
1646
-- | Helper to test that a given option is accepted OK with quick exit.
1647
checkEarlyExit name options param =
1648
  case CLI.parseOptsInner [param] name options of
1649
    Left (code, _) -> if code == 0
1650
                          then property True
1651
                          else failTest $ "Program " ++ name ++
1652
                                 " returns invalid code " ++ show code ++
1653
                                 " for option " ++ param
1654
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1655
         param ++ " as early exit one"
1656

    
1657
-- | Test that all binaries support some common options. There is
1658
-- nothing actually random about this test...
1659
prop_CLI_stdopts =
1660
  let params = ["-h", "--help", "-V", "--version"]
1661
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1662
      -- apply checkEarlyExit across the cartesian product of params and opts
1663
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1664

    
1665
testSuite "CLI"
1666
          [ 'prop_CLI_parseISpec
1667
          , 'prop_CLI_parseISpecFail
1668
          , 'prop_CLI_parseYesNo
1669
          , 'prop_CLI_StringArg
1670
          , 'prop_CLI_stdopts
1671
          ]
1672

    
1673
-- * JSON tests
1674

    
1675
prop_JSON_toArray :: [Int] -> Property
1676
prop_JSON_toArray intarr =
1677
  let arr = map J.showJSON intarr in
1678
  case JSON.toArray (J.JSArray arr) of
1679
    Types.Ok arr' -> arr ==? arr'
1680
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1681

    
1682
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1683
prop_JSON_toArrayFail i s b =
1684
  -- poor man's instance Arbitrary JSValue
1685
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1686
  case JSON.toArray item of
1687
    Types.Bad _ -> property True
1688
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1689

    
1690
testSuite "JSON"
1691
          [ 'prop_JSON_toArray
1692
          , 'prop_JSON_toArrayFail
1693
          ]
1694

    
1695
-- * Luxi tests
1696

    
1697
instance Arbitrary Luxi.LuxiReq where
1698
  arbitrary = elements [minBound..maxBound]
1699

    
1700
instance Arbitrary Luxi.QrViaLuxi where
1701
  arbitrary = elements [minBound..maxBound]
1702

    
1703
instance Arbitrary Luxi.LuxiOp where
1704
  arbitrary = do
1705
    lreq <- arbitrary
1706
    case lreq of
1707
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> arbitrary
1708
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1709
                            getFields <*> arbitrary
1710
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1711
                             arbitrary <*> arbitrary
1712
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1713
                                getFields <*> arbitrary
1714
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1715
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1716
                              (listOf getFQDN) <*> arbitrary
1717
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1718
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1719
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> getName <*> getFQDN
1720
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1721
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1722
                                (resize maxOpCodes arbitrary)
1723
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1724
                                  getFields <*> pure J.JSNull <*>
1725
                                  pure J.JSNull <*> arbitrary
1726
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1727
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1728
                                 arbitrary
1729
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1730
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1731
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1732

    
1733
-- | Simple check that encoding/decoding of LuxiOp works.
1734
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1735
prop_Luxi_CallEncoding op =
1736
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1737

    
1738
testSuite "LUXI"
1739
          [ 'prop_Luxi_CallEncoding
1740
          ]
1741

    
1742
-- * Ssconf tests
1743

    
1744
instance Arbitrary Ssconf.SSKey where
1745
  arbitrary = elements [minBound..maxBound]
1746

    
1747
prop_Ssconf_filename key =
1748
  printTestCase "Key doesn't start with correct prefix" $
1749
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1750

    
1751
testSuite "Ssconf"
1752
  [ 'prop_Ssconf_filename
1753
  ]