Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 5cefb2b2

History | View | Annotate | Download (63.7 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
  ) where
44

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

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

    
80
import qualified Ganeti.HTools.Program as Program
81
import qualified Ganeti.HTools.Program.Hail
82
import qualified Ganeti.HTools.Program.Hbal
83
import qualified Ganeti.HTools.Program.Hscan
84
import qualified Ganeti.HTools.Program.Hspace
85

    
86
import Ganeti.HTools.QCHelper (testSuite)
87

    
88
-- * Constants
89

    
90
-- | Maximum memory (1TiB, somewhat random value).
91
maxMem :: Int
92
maxMem = 1024 * 1024
93

    
94
-- | Maximum disk (8TiB, somewhat random value).
95
maxDsk :: Int
96
maxDsk = 1024 * 1024 * 8
97

    
98
-- | Max CPUs (1024, somewhat random value).
99
maxCpu :: Int
100
maxCpu = 1024
101

    
102
-- | Max vcpu ratio (random value).
103
maxVcpuRatio :: Double
104
maxVcpuRatio = 1024.0
105

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

    
110
-- | Max nodes, used just to limit arbitrary instances for smaller
111
-- opcode definitions (e.g. list of nodes in OpTestDelay).
112
maxNodes :: Int
113
maxNodes = 32
114

    
115
-- | Max opcodes or jobs in a submit job and submit many jobs.
116
maxOpCodes :: Int
117
maxOpCodes = 16
118

    
119
-- | All disk templates (used later)
120
allDiskTemplates :: [Types.DiskTemplate]
121
allDiskTemplates = [minBound..maxBound]
122

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

    
152

    
153
defGroup :: Group.Group
154
defGroup = flip Group.setIdx 0 $
155
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
156
                  nullIPolicy
157

    
158
defGroupList :: Group.List
159
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
160

    
161
defGroupAssoc :: Data.Map.Map String Types.Gdx
162
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
163

    
164
-- * Helper functions
165

    
166
-- | Simple checker for whether OpResult is fail or pass.
167
isFailure :: Types.OpResult a -> Bool
168
isFailure (Types.OpFail _) = True
169
isFailure _ = False
170

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

    
178
-- | Show a message and fail the test.
179
failTest :: String -> Property
180
failTest msg = printTestCase msg False
181

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

    
189
-- | Create an instance given its spec.
190
createInstance mem dsk vcpus =
191
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
192
    Types.DTDrbd8 1
193

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

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

    
214
-- | Checks if a node is "big" enough.
215
isNodeBig :: Int -> Node.Node -> Bool
216
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
217
                      && Node.availMem node > size * Types.unitMem
218
                      && Node.availCpu node > size * Types.unitCpu
219

    
220
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
221
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
222

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

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

    
249
-- | Checks if an instance is mirrored.
250
isMirrored :: Instance.Instance -> Bool
251
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
252

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

    
259
-- * Arbitrary instances
260

    
261
-- | Defines a DNS name.
262
newtype DNSChar = DNSChar { dnsGetChar::Char }
263

    
264
instance Arbitrary DNSChar where
265
  arbitrary = do
266
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
267
    return (DNSChar x)
268

    
269
-- | Generates a single name component.
270
getName :: Gen String
271
getName = do
272
  n <- choose (1, 64)
273
  dn <- vector n
274
  return (map dnsGetChar dn)
275

    
276
-- | Generates an entire FQDN.
277
getFQDN :: Gen String
278
getFQDN = do
279
  ncomps <- choose (1, 4)
280
  names <- vectorOf ncomps getName
281
  return $ intercalate "." names
282

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

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

    
298
-- | Defines a tag type.
299
newtype TagChar = TagChar { tagGetChar :: Char }
300

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

    
306
instance Arbitrary TagChar where
307
  arbitrary = do
308
    c <- elements tagChar
309
    return (TagChar c)
310

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

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

    
330
instance Arbitrary Types.InstanceStatus where
331
    arbitrary = elements [minBound..maxBound]
332

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

    
346
-- | Generates an instance smaller than a node.
347
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
348
genInstanceSmallerThanNode node =
349
  genInstanceSmallerThan (Node.availMem node `div` 2)
350
                         (Node.availDisk node `div` 2)
351
                         (Node.availCpu node `div` 2)
352

    
353
-- let's generate a random instance
354
instance Arbitrary Instance.Instance where
355
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
356

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

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

    
397
-- and a random node
398
instance Arbitrary Node.Node where
399
  arbitrary = genNode Nothing Nothing
400

    
401
-- replace disks
402
instance Arbitrary OpCodes.ReplaceDisksMode where
403
  arbitrary = elements [minBound..maxBound]
404

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

    
427
instance Arbitrary Jobs.OpStatus where
428
  arbitrary = elements [minBound..maxBound]
429

    
430
instance Arbitrary Jobs.JobStatus where
431
  arbitrary = elements [minBound..maxBound]
432

    
433
newtype SmallRatio = SmallRatio Double deriving Show
434
instance Arbitrary SmallRatio where
435
  arbitrary = do
436
    v <- choose (0, 1)
437
    return $ SmallRatio v
438

    
439
instance Arbitrary Types.AllocPolicy where
440
  arbitrary = elements [minBound..maxBound]
441

    
442
instance Arbitrary Types.DiskTemplate where
443
  arbitrary = elements [minBound..maxBound]
444

    
445
instance Arbitrary Types.FailMode where
446
  arbitrary = elements [minBound..maxBound]
447

    
448
instance Arbitrary Types.EvacMode where
449
  arbitrary = elements [minBound..maxBound]
450

    
451
instance Arbitrary a => Arbitrary (Types.OpResult a) where
452
  arbitrary = arbitrary >>= \c ->
453
              if c
454
                then Types.OpGood <$> arbitrary
455
                else Types.OpFail <$> arbitrary
456

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

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

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

    
507
-- * Actual tests
508

    
509
-- ** Utils tests
510

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

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

    
523
-- | Split and join should always be idempotent.
524
prop_Utils_commaSplitJoin s =
525
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
526

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

    
537
-- | Test that functional if' behaves like the syntactic sugar if.
538
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
539
prop_Utils_if'if cnd a b =
540
  Utils.if' cnd a b ==? if cnd then a else b
541

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

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

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

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

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

    
600
-- ** PeerMap tests
601

    
602
-- | Make sure add is idempotent.
603
prop_PeerMap_addIdempotent pmap key em =
604
  fn puniq ==? fn (fn puniq)
605
    where _types = (pmap::PeerMap.PeerMap,
606
                    key::PeerMap.Key, em::PeerMap.Elem)
607
          fn = PeerMap.add key em
608
          puniq = PeerMap.accumArray const pmap
609

    
610
-- | Make sure remove is idempotent.
611
prop_PeerMap_removeIdempotent pmap key =
612
  fn puniq ==? fn (fn puniq)
613
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
614
          fn = PeerMap.remove key
615
          puniq = PeerMap.accumArray const pmap
616

    
617
-- | Make sure a missing item returns 0.
618
prop_PeerMap_findMissing pmap key =
619
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
620
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
621
          puniq = PeerMap.accumArray const pmap
622

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

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

    
637
-- | List of tests for the PeerMap module.
638
testSuite "PeerMap"
639
            [ 'prop_PeerMap_addIdempotent
640
            , 'prop_PeerMap_removeIdempotent
641
            , 'prop_PeerMap_maxElem
642
            , 'prop_PeerMap_addFind
643
            , 'prop_PeerMap_findMissing
644
            ]
645

    
646
-- ** Container tests
647

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

    
658
prop_Container_nameOf node =
659
  let nl = makeSmallCluster node 1
660
      fnode = head (Container.elems nl)
661
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
662

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

    
684
testSuite "Container"
685
            [ 'prop_Container_addTwo
686
            , 'prop_Container_nameOf
687
            , 'prop_Container_findByName
688
            ]
689

    
690
-- ** Instance tests
691

    
692
-- Simple instance tests, we only have setter/getters
693

    
694
prop_Instance_creat inst =
695
  Instance.name inst ==? Instance.alias inst
696

    
697
prop_Instance_setIdx inst idx =
698
  Instance.idx (Instance.setIdx inst idx) ==? idx
699
    where _types = (inst::Instance.Instance, idx::Types.Idx)
700

    
701
prop_Instance_setName inst name =
702
  Instance.name newinst == name &&
703
  Instance.alias newinst == name
704
    where _types = (inst::Instance.Instance, name::String)
705
          newinst = Instance.setName inst name
706

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

    
713
prop_Instance_setPri inst pdx =
714
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
715
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
716

    
717
prop_Instance_setSec inst sdx =
718
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
719
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
720

    
721
prop_Instance_setBoth inst pdx sdx =
722
  Instance.pNode si == pdx && Instance.sNode si == sdx
723
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
724
          si = Instance.setBoth inst pdx sdx
725

    
726
prop_Instance_shrinkMG inst =
727
  Instance.mem inst >= 2 * Types.unitMem ==>
728
    case Instance.shrinkByType inst Types.FailMem of
729
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
730
      _ -> False
731

    
732
prop_Instance_shrinkMF inst =
733
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
734
    let inst' = inst { Instance.mem = mem}
735
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
736

    
737
prop_Instance_shrinkCG inst =
738
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
739
    case Instance.shrinkByType inst Types.FailCPU of
740
      Types.Ok inst' ->
741
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
742
      _ -> False
743

    
744
prop_Instance_shrinkCF inst =
745
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
746
    let inst' = inst { Instance.vcpus = vcpus }
747
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
748

    
749
prop_Instance_shrinkDG inst =
750
  Instance.dsk inst >= 2 * Types.unitDsk ==>
751
    case Instance.shrinkByType inst Types.FailDisk of
752
      Types.Ok inst' ->
753
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
754
      _ -> False
755

    
756
prop_Instance_shrinkDF inst =
757
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
758
    let inst' = inst { Instance.dsk = dsk }
759
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
760

    
761
prop_Instance_setMovable inst m =
762
  Instance.movable inst' ==? m
763
    where inst' = Instance.setMovable inst m
764

    
765
testSuite "Instance"
766
            [ 'prop_Instance_creat
767
            , 'prop_Instance_setIdx
768
            , 'prop_Instance_setName
769
            , 'prop_Instance_setAlias
770
            , 'prop_Instance_setPri
771
            , 'prop_Instance_setSec
772
            , 'prop_Instance_setBoth
773
            , 'prop_Instance_shrinkMG
774
            , 'prop_Instance_shrinkMF
775
            , 'prop_Instance_shrinkCG
776
            , 'prop_Instance_shrinkCF
777
            , 'prop_Instance_shrinkDG
778
            , 'prop_Instance_shrinkDF
779
            , 'prop_Instance_setMovable
780
            ]
781

    
782
-- ** Backends
783

    
784
-- *** Text backend tests
785

    
786
-- Instance text loader tests
787

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

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

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

    
867
prop_Text_Load_NodeFail fields =
868
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
869

    
870
prop_Text_NodeLSIdempotent node =
871
  (Text.loadNode defGroupAssoc.
872
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
873
  Just (Node.name n, n)
874
    -- override failN1 to what loadNode returns by default
875
    where n = Node.setPolicy Types.defIPolicy $
876
              node { Node.failN1 = True, Node.offline = False }
877

    
878
prop_Text_ISpecIdempotent ispec =
879
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
880
       Text.serializeISpec $ ispec of
881
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
882
    Types.Ok ispec' -> ispec ==? ispec'
883

    
884
prop_Text_IPolicyIdempotent ipol =
885
  case Text.loadIPolicy . Utils.sepSplit '|' $
886
       Text.serializeIPolicy owner ipol of
887
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
888
    Types.Ok res -> (owner, ipol) ==? res
889
  where owner = "dummy"
890

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

    
925
testSuite "Text"
926
            [ 'prop_Text_Load_Instance
927
            , 'prop_Text_Load_InstanceFail
928
            , 'prop_Text_Load_Node
929
            , 'prop_Text_Load_NodeFail
930
            , 'prop_Text_NodeLSIdempotent
931
            , 'prop_Text_ISpecIdempotent
932
            , 'prop_Text_IPolicyIdempotent
933
            , 'prop_Text_CreateSerialise
934
            ]
935

    
936
-- *** Simu backend
937

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

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

    
983
testSuite "Simu"
984
            [ 'prop_SimuLoad
985
            ]
986

    
987
-- ** Node tests
988

    
989
prop_Node_setAlias node name =
990
  Node.name newnode == Node.name node &&
991
  Node.alias newnode == name
992
    where _types = (node::Node.Node, name::String)
993
          newnode = Node.setAlias node name
994

    
995
prop_Node_setOffline node status =
996
  Node.offline newnode ==? status
997
    where newnode = Node.setOffline node status
998

    
999
prop_Node_setXmem node xm =
1000
  Node.xMem newnode ==? xm
1001
    where newnode = Node.setXmem node xm
1002

    
1003
prop_Node_setMcpu node mc =
1004
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1005
    where newnode = Node.setMcpu node mc
1006

    
1007
-- | Check that an instance add with too high memory or disk will be
1008
-- rejected.
1009
prop_Node_addPriFM node inst =
1010
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1011
  not (Instance.isOffline inst) ==>
1012
  case Node.addPri node inst'' of
1013
    Types.OpFail Types.FailMem -> True
1014
    _ -> False
1015
  where _types = (node::Node.Node, inst::Instance.Instance)
1016
        inst' = setInstanceSmallerThanNode node inst
1017
        inst'' = inst' { Instance.mem = Instance.mem inst }
1018

    
1019
-- | Check that adding a primary instance with too much disk fails
1020
-- with type FailDisk.
1021
prop_Node_addPriFD node inst =
1022
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1023
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1024
  let inst' = setInstanceSmallerThanNode node inst
1025
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1026
                     , Instance.diskTemplate = dt }
1027
  in case Node.addPri node inst'' of
1028
       Types.OpFail Types.FailDisk -> True
1029
       _ -> False
1030

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

    
1043
-- | Check that an instance add with too high memory or disk will be
1044
-- rejected.
1045
prop_Node_addSec node inst pdx =
1046
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1047
    not (Instance.isOffline inst)) ||
1048
   Instance.dsk inst >= Node.fDsk node) &&
1049
  not (Node.failN1 node) ==>
1050
      isFailure (Node.addSec node inst pdx)
1051
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
1052

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

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

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

    
1111
-- | Check mdsk setting.
1112
prop_Node_setMdsk node mx =
1113
  Node.loDsk node' >= 0 &&
1114
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1115
  Node.availDisk node' >= 0 &&
1116
  Node.availDisk node' <= Node.fDsk node' &&
1117
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1118
  Node.mDsk node' == mx'
1119
    where _types = (node::Node.Node, mx::SmallRatio)
1120
          node' = Node.setMdsk node mx'
1121
          SmallRatio mx' = mx
1122

    
1123
-- Check tag maps
1124
prop_Node_tagMaps_idempotent =
1125
  forAll genTags $ \tags ->
1126
  Node.delTags (Node.addTags m tags) tags ==? m
1127
    where m = Data.Map.empty
1128

    
1129
prop_Node_tagMaps_reject =
1130
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1131
  let m = Node.addTags Data.Map.empty tags
1132
  in all (\t -> Node.rejectAddTags m [t]) tags
1133

    
1134
prop_Node_showField node =
1135
  forAll (elements Node.defaultFields) $ \ field ->
1136
  fst (Node.showHeader field) /= Types.unknownField &&
1137
  Node.showField node field /= Types.unknownField
1138

    
1139
prop_Node_computeGroups nodes =
1140
  let ng = Node.computeGroups nodes
1141
      onlyuuid = map fst ng
1142
  in length nodes == sum (map (length . snd) ng) &&
1143
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1144
     length (nub onlyuuid) == length onlyuuid &&
1145
     (null nodes || not (null ng))
1146

    
1147
-- Check idempotence of add/remove operations
1148
prop_Node_addPri_idempotent =
1149
  forAll genOnlineNode $ \node ->
1150
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1151
  case Node.addPri node inst of
1152
    Types.OpGood node' -> Node.removePri node' inst ==? node
1153
    _ -> failTest "Can't add instance"
1154

    
1155
prop_Node_addSec_idempotent =
1156
  forAll genOnlineNode $ \node ->
1157
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1158
  let pdx = Node.idx node + 1
1159
      inst' = Instance.setPri inst pdx
1160
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1161
  in case Node.addSec node inst'' pdx of
1162
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1163
       _ -> failTest "Can't add instance"
1164

    
1165
testSuite "Node"
1166
            [ 'prop_Node_setAlias
1167
            , 'prop_Node_setOffline
1168
            , 'prop_Node_setMcpu
1169
            , 'prop_Node_setXmem
1170
            , 'prop_Node_addPriFM
1171
            , 'prop_Node_addPriFD
1172
            , 'prop_Node_addPriFC
1173
            , 'prop_Node_addSec
1174
            , 'prop_Node_addOfflinePri
1175
            , 'prop_Node_addOfflineSec
1176
            , 'prop_Node_rMem
1177
            , 'prop_Node_setMdsk
1178
            , 'prop_Node_tagMaps_idempotent
1179
            , 'prop_Node_tagMaps_reject
1180
            , 'prop_Node_showField
1181
            , 'prop_Node_computeGroups
1182
            , 'prop_Node_addPri_idempotent
1183
            , 'prop_Node_addSec_idempotent
1184
            ]
1185

    
1186
-- ** Cluster tests
1187

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

    
1201
-- | Check that cluster stats are sane.
1202
prop_CStats_sane =
1203
  forAll (choose (1, 1024)) $ \count ->
1204
  forAll genOnlineNode $ \node ->
1205
  let fn = Node.buildPeers node Container.empty
1206
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1207
      nl = Container.fromList nlst
1208
      cstats = Cluster.totalResources nl
1209
  in Cluster.csAdsk cstats >= 0 &&
1210
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1211

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

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

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

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

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

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

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

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

    
1373
-- | Checks consistency.
1374
prop_ClusterCheckConsistency node inst =
1375
  let nl = makeSmallCluster node 3
1376
      [node1, node2, node3] = Container.elems nl
1377
      node3' = node3 { Node.group = 1 }
1378
      nl' = Container.add (Node.idx node3') node3' nl
1379
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1380
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1381
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1382
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1383
  in null (ccheck [(0, inst1)]) &&
1384
     null (ccheck [(0, inst2)]) &&
1385
     (not . null $ ccheck [(0, inst3)])
1386

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

    
1398
-- | Helper function to check if we can allocate an instance on a
1399
-- given node list.
1400
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1401
canAllocOn nl reqnodes inst =
1402
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1403
       Cluster.tryAlloc nl (Container.empty) inst of
1404
       Types.Bad _ -> False
1405
       Types.Ok as ->
1406
         case Cluster.asSolution as of
1407
           Nothing -> False
1408
           Just _ -> True
1409

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

    
1427
testSuite "Cluster"
1428
            [ 'prop_Score_Zero
1429
            , 'prop_CStats_sane
1430
            , 'prop_ClusterAlloc_sane
1431
            , 'prop_ClusterCanTieredAlloc
1432
            , 'prop_ClusterAllocRelocate
1433
            , 'prop_ClusterAllocEvacuate
1434
            , 'prop_ClusterAllocChangeGroup
1435
            , 'prop_ClusterAllocBalance
1436
            , 'prop_ClusterCheckConsistency
1437
            , 'prop_ClusterSplitCluster
1438
            , 'prop_ClusterAllocPolicy
1439
            ]
1440

    
1441
-- ** OpCodes tests
1442

    
1443
-- | Check that opcode serialization is idempotent.
1444
prop_OpCodes_serialization op =
1445
  case J.readJSON (J.showJSON op) of
1446
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1447
    J.Ok op' -> op ==? op'
1448
  where _types = op::OpCodes.OpCode
1449

    
1450
testSuite "OpCodes"
1451
            [ 'prop_OpCodes_serialization ]
1452

    
1453
-- ** Jobs tests
1454

    
1455
-- | Check that (queued) job\/opcode status serialization is idempotent.
1456
prop_OpStatus_serialization os =
1457
  case J.readJSON (J.showJSON os) of
1458
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1459
    J.Ok os' -> os ==? os'
1460
  where _types = os::Jobs.OpStatus
1461

    
1462
prop_JobStatus_serialization js =
1463
  case J.readJSON (J.showJSON js) of
1464
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1465
    J.Ok js' -> js ==? js'
1466
  where _types = js::Jobs.JobStatus
1467

    
1468
testSuite "Jobs"
1469
            [ 'prop_OpStatus_serialization
1470
            , 'prop_JobStatus_serialization
1471
            ]
1472

    
1473
-- ** Loader tests
1474

    
1475
prop_Loader_lookupNode ktn inst node =
1476
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1477
    where nl = Data.Map.fromList ktn
1478

    
1479
prop_Loader_lookupInstance kti inst =
1480
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1481
    where il = Data.Map.fromList kti
1482

    
1483
prop_Loader_assignIndices =
1484
  -- generate nodes with unique names
1485
  forAll (arbitrary `suchThat`
1486
          (\nodes ->
1487
             let names = map Node.name nodes
1488
             in length names == length (nub names))) $ \nodes ->
1489
  let (nassoc, kt) =
1490
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1491
  in Data.Map.size nassoc == length nodes &&
1492
     Container.size kt == length nodes &&
1493
     if not (null nodes)
1494
       then maximum (IntMap.keys kt) == length nodes - 1
1495
       else True
1496

    
1497
-- | Checks that the number of primary instances recorded on the nodes
1498
-- is zero.
1499
prop_Loader_mergeData ns =
1500
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1501
  in case Loader.mergeData [] [] [] []
1502
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1503
    Types.Bad _ -> False
1504
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1505
      let nodes = Container.elems nl
1506
          instances = Container.elems il
1507
      in (sum . map (length . Node.pList)) nodes == 0 &&
1508
         null instances
1509

    
1510
-- | Check that compareNameComponent on equal strings works.
1511
prop_Loader_compareNameComponent_equal :: String -> Bool
1512
prop_Loader_compareNameComponent_equal s =
1513
  Loader.compareNameComponent s s ==
1514
    Loader.LookupResult Loader.ExactMatch s
1515

    
1516
-- | Check that compareNameComponent on prefix strings works.
1517
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1518
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1519
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1520
    Loader.LookupResult Loader.PartialMatch s1
1521

    
1522
testSuite "Loader"
1523
            [ 'prop_Loader_lookupNode
1524
            , 'prop_Loader_lookupInstance
1525
            , 'prop_Loader_assignIndices
1526
            , 'prop_Loader_mergeData
1527
            , 'prop_Loader_compareNameComponent_equal
1528
            , 'prop_Loader_compareNameComponent_prefix
1529
            ]
1530

    
1531
-- ** Types tests
1532

    
1533
prop_Types_AllocPolicy_serialisation apol =
1534
  case J.readJSON (J.showJSON apol) of
1535
    J.Ok p -> p ==? apol
1536
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1537
      where _types = apol::Types.AllocPolicy
1538

    
1539
prop_Types_DiskTemplate_serialisation dt =
1540
  case J.readJSON (J.showJSON dt) of
1541
    J.Ok p -> p ==? dt
1542
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1543
      where _types = dt::Types.DiskTemplate
1544

    
1545
prop_Types_ISpec_serialisation ispec =
1546
  case J.readJSON (J.showJSON ispec) of
1547
    J.Ok p -> p ==? ispec
1548
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1549
      where _types = ispec::Types.ISpec
1550

    
1551
prop_Types_IPolicy_serialisation ipol =
1552
  case J.readJSON (J.showJSON ipol) of
1553
    J.Ok p -> p ==? ipol
1554
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1555
      where _types = ipol::Types.IPolicy
1556

    
1557
prop_Types_EvacMode_serialisation em =
1558
  case J.readJSON (J.showJSON em) of
1559
    J.Ok p -> p ==? em
1560
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1561
      where _types = em::Types.EvacMode
1562

    
1563
prop_Types_opToResult op =
1564
  case op of
1565
    Types.OpFail _ -> Types.isBad r
1566
    Types.OpGood v -> case r of
1567
                        Types.Bad _ -> False
1568
                        Types.Ok v' -> v == v'
1569
  where r = Types.opToResult op
1570
        _types = op::Types.OpResult Int
1571

    
1572
prop_Types_eitherToResult ei =
1573
  case ei of
1574
    Left _ -> Types.isBad r
1575
    Right v -> case r of
1576
                 Types.Bad _ -> False
1577
                 Types.Ok v' -> v == v'
1578
    where r = Types.eitherToResult ei
1579
          _types = ei::Either String Int
1580

    
1581
testSuite "Types"
1582
            [ 'prop_Types_AllocPolicy_serialisation
1583
            , 'prop_Types_DiskTemplate_serialisation
1584
            , 'prop_Types_ISpec_serialisation
1585
            , 'prop_Types_IPolicy_serialisation
1586
            , 'prop_Types_EvacMode_serialisation
1587
            , 'prop_Types_opToResult
1588
            , 'prop_Types_eitherToResult
1589
            ]
1590

    
1591
-- ** CLI tests
1592

    
1593
-- | Test correct parsing.
1594
prop_CLI_parseISpec descr dsk mem cpu =
1595
  let str = printf "%d,%d,%d" dsk mem cpu
1596
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1597

    
1598
-- | Test parsing failure due to wrong section count.
1599
prop_CLI_parseISpecFail descr =
1600
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1601
  forAll (replicateM nelems arbitrary) $ \values ->
1602
  let str = intercalate "," $ map show (values::[Int])
1603
  in case CLI.parseISpecString descr str of
1604
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1605
       _ -> property True
1606

    
1607
-- | Test parseYesNo.
1608
prop_CLI_parseYesNo def testval val =
1609
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1610
  if testval
1611
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1612
    else let result = CLI.parseYesNo def (Just actual_val)
1613
         in if actual_val `elem` ["yes", "no"]
1614
              then result ==? Types.Ok (actual_val == "yes")
1615
              else property $ Types.isBad result
1616

    
1617
-- | Helper to check for correct parsing of string arg.
1618
checkStringArg val (opt, fn) =
1619
  let GetOpt.Option _ longs _ _ = opt
1620
  in case longs of
1621
       [] -> failTest "no long options?"
1622
       cmdarg:_ ->
1623
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1624
           Left e -> failTest $ "Failed to parse option: " ++ show e
1625
           Right (options, _) -> fn options ==? Just val
1626

    
1627
-- | Test a few string arguments.
1628
prop_CLI_StringArg argument =
1629
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1630
             , (CLI.oDynuFile,      CLI.optDynuFile)
1631
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1632
             , (CLI.oReplay,        CLI.optReplay)
1633
             , (CLI.oPrintCommands, CLI.optShowCmds)
1634
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1635
             ]
1636
  in conjoin $ map (checkStringArg argument) args
1637

    
1638
-- | Helper to test that a given option is accepted OK with quick exit.
1639
checkEarlyExit name options param =
1640
  case CLI.parseOptsInner [param] name options of
1641
    Left (code, _) -> if code == 0
1642
                          then property True
1643
                          else failTest $ "Program " ++ name ++
1644
                                 " returns invalid code " ++ show code ++
1645
                                 " for option " ++ param
1646
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1647
         param ++ " as early exit one"
1648

    
1649
-- | Test that all binaries support some common options. There is
1650
-- nothing actually random about this test...
1651
prop_CLI_stdopts =
1652
  let params = ["-h", "--help", "-V", "--version"]
1653
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1654
      -- apply checkEarlyExit across the cartesian product of params and opts
1655
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1656

    
1657
testSuite "CLI"
1658
          [ 'prop_CLI_parseISpec
1659
          , 'prop_CLI_parseISpecFail
1660
          , 'prop_CLI_parseYesNo
1661
          , 'prop_CLI_StringArg
1662
          , 'prop_CLI_stdopts
1663
          ]
1664

    
1665
-- * JSON tests
1666

    
1667
prop_JSON_toArray :: [Int] -> Property
1668
prop_JSON_toArray intarr =
1669
  let arr = map J.showJSON intarr in
1670
  case JSON.toArray (J.JSArray arr) of
1671
    Types.Ok arr' -> arr ==? arr'
1672
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1673

    
1674
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1675
prop_JSON_toArrayFail i s b =
1676
  -- poor man's instance Arbitrary JSValue
1677
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1678
  case JSON.toArray item of
1679
    Types.Bad _ -> property True
1680
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1681

    
1682
testSuite "JSON"
1683
          [ 'prop_JSON_toArray
1684
          , 'prop_JSON_toArrayFail
1685
          ]