Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (62.2 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittests for ganeti-htools.
4

    
5
-}
6

    
7
{-
8

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

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

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

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

    
26
-}
27

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

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

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

    
78
import qualified Ganeti.HTools.Program as Program
79
import qualified Ganeti.HTools.Program.Hail
80
import qualified Ganeti.HTools.Program.Hbal
81
import qualified Ganeti.HTools.Program.Hscan
82
import qualified Ganeti.HTools.Program.Hspace
83

    
84
import Ganeti.HTools.QCHelper (testSuite)
85

    
86
-- * Constants
87

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

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

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

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

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

    
108
-- | All disk templates (used later)
109
allDiskTemplates :: [Types.DiskTemplate]
110
allDiskTemplates = [minBound..maxBound]
111

    
112
-- | Null iPolicy, and by null we mean very liberal.
113
nullIPolicy = Types.IPolicy
114
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
115
                                       , Types.iSpecCpuCount   = 0
116
                                       , Types.iSpecDiskSize   = 0
117
                                       , Types.iSpecDiskCount  = 0
118
                                       , Types.iSpecNicCount   = 0
119
                                       , Types.iSpecSpindleUse = 0
120
                                       }
121
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
122
                                       , Types.iSpecCpuCount   = maxBound
123
                                       , Types.iSpecDiskSize   = maxBound
124
                                       , Types.iSpecDiskCount  = C.maxDisks
125
                                       , Types.iSpecNicCount   = C.maxNics
126
                                       , Types.iSpecSpindleUse = maxBound
127
                                       }
128
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
129
                                       , Types.iSpecCpuCount   = Types.unitCpu
130
                                       , Types.iSpecDiskSize   = Types.unitDsk
131
                                       , Types.iSpecDiskCount  = 1
132
                                       , Types.iSpecNicCount   = 1
133
                                       , Types.iSpecSpindleUse = 1
134
                                       }
135
  , Types.iPolicyDiskTemplates = [Types.DTDrbd8, Types.DTPlain]
136
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
137
                                          -- enough to not impact us
138
  , Types.iPolicySpindleRatio = maxSpindleRatio
139
  }
140

    
141

    
142
defGroup :: Group.Group
143
defGroup = flip Group.setIdx 0 $
144
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
145
                  nullIPolicy
146

    
147
defGroupList :: Group.List
148
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
149

    
150
defGroupAssoc :: Data.Map.Map String Types.Gdx
151
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
152

    
153
-- * Helper functions
154

    
155
-- | Simple checker for whether OpResult is fail or pass.
156
isFailure :: Types.OpResult a -> Bool
157
isFailure (Types.OpFail _) = True
158
isFailure _ = False
159

    
160
-- | Checks for equality with proper annotation.
161
(==?) :: (Show a, Eq a) => a -> a -> Property
162
(==?) x y = printTestCase
163
            ("Expected equality, but '" ++
164
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
165
infix 3 ==?
166

    
167
-- | Show a message and fail the test.
168
failTest :: String -> Property
169
failTest msg = printTestCase msg False
170

    
171
-- | Update an instance to be smaller than a node.
172
setInstanceSmallerThanNode node inst =
173
  inst { Instance.mem = Node.availMem node `div` 2
174
       , Instance.dsk = Node.availDisk node `div` 2
175
       , Instance.vcpus = Node.availCpu node `div` 2
176
       }
177

    
178
-- | Create an instance given its spec.
179
createInstance mem dsk vcpus =
180
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
181
    Types.DTDrbd8 1
182

    
183
-- | Create a small cluster by repeating a node spec.
184
makeSmallCluster :: Node.Node -> Int -> Node.List
185
makeSmallCluster node count =
186
  let origname = Node.name node
187
      origalias = Node.alias node
188
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
189
                                , Node.alias = origalias ++ "-" ++ show idx })
190
              [1..count]
191
      fn = flip Node.buildPeers Container.empty
192
      namelst = map (\n -> (Node.name n, fn n)) nodes
193
      (_, nlst) = Loader.assignIndices namelst
194
  in nlst
195

    
196
-- | Make a small cluster, both nodes and instances.
197
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
198
                      -> (Node.List, Instance.List, Instance.Instance)
199
makeSmallEmptyCluster node count inst =
200
  (makeSmallCluster node count, Container.empty,
201
   setInstanceSmallerThanNode node inst)
202

    
203
-- | Checks if a node is "big" enough.
204
isNodeBig :: Int -> Node.Node -> Bool
205
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
206
                      && Node.availMem node > size * Types.unitMem
207
                      && Node.availCpu node > size * Types.unitCpu
208

    
209
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
210
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
211

    
212
-- | Assigns a new fresh instance to a cluster; this is not
213
-- allocation, so no resource checks are done.
214
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
215
                  Types.Idx -> Types.Idx ->
216
                  (Node.List, Instance.List)
217
assignInstance nl il inst pdx sdx =
218
  let pnode = Container.find pdx nl
219
      snode = Container.find sdx nl
220
      maxiidx = if Container.null il
221
                  then 0
222
                  else fst (Container.findMax il) + 1
223
      inst' = inst { Instance.idx = maxiidx,
224
                     Instance.pNode = pdx, Instance.sNode = sdx }
225
      pnode' = Node.setPri pnode inst'
226
      snode' = Node.setSec snode inst'
227
      nl' = Container.addTwo pdx pnode' sdx snode' nl
228
      il' = Container.add maxiidx inst' il
229
  in (nl', il')
230

    
231
-- | Generates a list of a given size with non-duplicate elements.
232
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
233
genUniquesList cnt =
234
  foldM (\lst _ -> do
235
           newelem <- arbitrary `suchThat` (`notElem` lst)
236
           return (newelem:lst)) [] [1..cnt]
237

    
238
-- | Checks if an instance is mirrored.
239
isMirrored :: Instance.Instance -> Bool
240
isMirrored =
241
  (/= Types.MirrorNone) . Types.templateMirrorType . Instance.diskTemplate
242

    
243
-- | Returns the possible change node types for a disk template.
244
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
245
evacModeOptions Types.MirrorNone     = []
246
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
247
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
248

    
249
-- * Arbitrary instances
250

    
251
-- | Defines a DNS name.
252
newtype DNSChar = DNSChar { dnsGetChar::Char }
253

    
254
instance Arbitrary DNSChar where
255
  arbitrary = do
256
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
257
    return (DNSChar x)
258

    
259
-- | Generates a single name component.
260
getName :: Gen String
261
getName = do
262
  n <- choose (1, 64)
263
  dn <- vector n::Gen [DNSChar]
264
  return (map dnsGetChar dn)
265

    
266
-- | Generates an entire FQDN.
267
getFQDN :: Gen String
268
getFQDN = do
269
  ncomps <- choose (1, 4)
270
  names <- mapM (const getName) [1..ncomps::Int]
271
  return $ intercalate "." names
272

    
273
-- | Defines a tag type.
274
newtype TagChar = TagChar { tagGetChar :: Char }
275

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

    
281
instance Arbitrary TagChar where
282
  arbitrary = do
283
    c <- elements tagChar
284
    return (TagChar c)
285

    
286
-- | Generates a tag
287
genTag :: Gen [TagChar]
288
genTag = do
289
  -- the correct value would be C.maxTagLen, but that's way too
290
  -- verbose in unittests, and at the moment I don't see any possible
291
  -- bugs with longer tags and the way we use tags in htools
292
  n <- choose (1, 10)
293
  vector n
294

    
295
-- | Generates a list of tags (correctly upper bounded).
296
genTags :: Gen [String]
297
genTags = do
298
  -- the correct value would be C.maxTagsPerObj, but per the comment
299
  -- in genTag, we don't use tags enough in htools to warrant testing
300
  -- such big values
301
  n <- choose (0, 10::Int)
302
  tags <- mapM (const genTag) [1..n]
303
  return $ map (map tagGetChar) tags
304

    
305
instance Arbitrary Types.InstanceStatus where
306
    arbitrary = elements [minBound..maxBound]
307

    
308
-- | Generates a random instance with maximum disk/mem/cpu values.
309
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
310
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
311
  name <- getFQDN
312
  mem <- choose (0, lim_mem)
313
  dsk <- choose (0, lim_dsk)
314
  run_st <- arbitrary
315
  pn <- arbitrary
316
  sn <- arbitrary
317
  vcpus <- choose (0, lim_cpu)
318
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn
319
         Types.DTDrbd8 1
320

    
321
-- | Generates an instance smaller than a node.
322
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
323
genInstanceSmallerThanNode node =
324
  genInstanceSmallerThan (Node.availMem node `div` 2)
325
                         (Node.availDisk node `div` 2)
326
                         (Node.availCpu node `div` 2)
327

    
328
-- let's generate a random instance
329
instance Arbitrary Instance.Instance where
330
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
331

    
332
-- | Generas an arbitrary node based on sizing information.
333
genNode :: Maybe Int -- ^ Minimum node size in terms of units
334
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
335
                     -- just by the max... constants)
336
        -> Gen Node.Node
337
genNode min_multiplier max_multiplier = do
338
  let (base_mem, base_dsk, base_cpu) =
339
        case min_multiplier of
340
          Just mm -> (mm * Types.unitMem,
341
                      mm * Types.unitDsk,
342
                      mm * Types.unitCpu)
343
          Nothing -> (0, 0, 0)
344
      (top_mem, top_dsk, top_cpu)  =
345
        case max_multiplier of
346
          Just mm -> (mm * Types.unitMem,
347
                      mm * Types.unitDsk,
348
                      mm * Types.unitCpu)
349
          Nothing -> (maxMem, maxDsk, maxCpu)
350
  name  <- getFQDN
351
  mem_t <- choose (base_mem, top_mem)
352
  mem_f <- choose (base_mem, mem_t)
353
  mem_n <- choose (0, mem_t - mem_f)
354
  dsk_t <- choose (base_dsk, top_dsk)
355
  dsk_f <- choose (base_dsk, dsk_t)
356
  cpu_t <- choose (base_cpu, top_cpu)
357
  offl  <- arbitrary
358
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
359
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
360
      n' = Node.setPolicy nullIPolicy n
361
  return $ Node.buildPeers n' Container.empty
362

    
363
-- | Helper function to generate a sane node.
364
genOnlineNode :: Gen Node.Node
365
genOnlineNode = do
366
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
367
                              not (Node.failN1 n) &&
368
                              Node.availDisk n > 0 &&
369
                              Node.availMem n > 0 &&
370
                              Node.availCpu n > 0)
371

    
372
-- and a random node
373
instance Arbitrary Node.Node where
374
  arbitrary = genNode Nothing Nothing
375

    
376
-- replace disks
377
instance Arbitrary OpCodes.ReplaceDisksMode where
378
  arbitrary = elements [minBound..maxBound]
379

    
380
instance Arbitrary OpCodes.OpCode where
381
  arbitrary = do
382
    op_id <- elements [ "OP_TEST_DELAY"
383
                      , "OP_INSTANCE_REPLACE_DISKS"
384
                      , "OP_INSTANCE_FAILOVER"
385
                      , "OP_INSTANCE_MIGRATE"
386
                      ]
387
    case op_id of
388
      "OP_TEST_DELAY" ->
389
        liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
390
      "OP_INSTANCE_REPLACE_DISKS" ->
391
        liftM5 OpCodes.OpInstanceReplaceDisks arbitrary arbitrary
392
          arbitrary arbitrary arbitrary
393
      "OP_INSTANCE_FAILOVER" ->
394
        liftM3 OpCodes.OpInstanceFailover arbitrary arbitrary
395
          arbitrary
396
      "OP_INSTANCE_MIGRATE" ->
397
        liftM5 OpCodes.OpInstanceMigrate arbitrary arbitrary
398
          arbitrary arbitrary arbitrary
399
      _ -> fail "Wrong opcode"
400

    
401
instance Arbitrary Jobs.OpStatus where
402
  arbitrary = elements [minBound..maxBound]
403

    
404
instance Arbitrary Jobs.JobStatus where
405
  arbitrary = elements [minBound..maxBound]
406

    
407
newtype SmallRatio = SmallRatio Double deriving Show
408
instance Arbitrary SmallRatio where
409
  arbitrary = do
410
    v <- choose (0, 1)
411
    return $ SmallRatio v
412

    
413
instance Arbitrary Types.AllocPolicy where
414
  arbitrary = elements [minBound..maxBound]
415

    
416
instance Arbitrary Types.DiskTemplate where
417
  arbitrary = elements [minBound..maxBound]
418

    
419
instance Arbitrary Types.FailMode where
420
  arbitrary = elements [minBound..maxBound]
421

    
422
instance Arbitrary Types.EvacMode where
423
  arbitrary = elements [minBound..maxBound]
424

    
425
instance Arbitrary a => Arbitrary (Types.OpResult a) where
426
  arbitrary = arbitrary >>= \c ->
427
              if c
428
                then liftM Types.OpGood arbitrary
429
                else liftM Types.OpFail arbitrary
430

    
431
instance Arbitrary Types.ISpec where
432
  arbitrary = do
433
    mem_s <- arbitrary::Gen (NonNegative Int)
434
    dsk_c <- arbitrary::Gen (NonNegative Int)
435
    dsk_s <- arbitrary::Gen (NonNegative Int)
436
    cpu_c <- arbitrary::Gen (NonNegative Int)
437
    nic_c <- arbitrary::Gen (NonNegative Int)
438
    su    <- arbitrary::Gen (NonNegative Int)
439
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
440
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
441
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
442
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
443
                       , Types.iSpecNicCount   = fromIntegral nic_c
444
                       , Types.iSpecSpindleUse = fromIntegral su
445
                       }
446

    
447
-- | Generates an ispec bigger than the given one.
448
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
449
genBiggerISpec imin = do
450
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
451
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
452
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
453
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
454
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
455
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
456
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
457
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
458
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
459
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
460
                     , Types.iSpecNicCount   = fromIntegral nic_c
461
                     , Types.iSpecSpindleUse = fromIntegral su
462
                     }
463

    
464
instance Arbitrary Types.IPolicy where
465
  arbitrary = do
466
    imin <- arbitrary
467
    istd <- genBiggerISpec imin
468
    imax <- genBiggerISpec istd
469
    num_tmpl <- choose (0, length allDiskTemplates)
470
    dts  <- genUniquesList num_tmpl
471
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
472
    spindle_ratio <- choose (1.0, maxSpindleRatio)
473
    return Types.IPolicy { Types.iPolicyMinSpec = imin
474
                         , Types.iPolicyStdSpec = istd
475
                         , Types.iPolicyMaxSpec = imax
476
                         , Types.iPolicyDiskTemplates = dts
477
                         , Types.iPolicyVcpuRatio = vcpu_ratio
478
                         , Types.iPolicySpindleRatio = spindle_ratio
479
                         }
480

    
481
-- * Actual tests
482

    
483
-- ** Utils tests
484

    
485
-- | Helper to generate a small string that doesn't contain commas.
486
genNonCommaString = do
487
  size <- choose (0, 20) -- arbitrary max size
488
  vectorOf size (arbitrary `suchThat` ((/=) ','))
489

    
490
-- | If the list is not just an empty element, and if the elements do
491
-- not contain commas, then join+split should be idempotent.
492
prop_Utils_commaJoinSplit =
493
  forAll (choose (0, 20)) $ \llen ->
494
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
495
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
496

    
497
-- | Split and join should always be idempotent.
498
prop_Utils_commaSplitJoin s =
499
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
500

    
501
-- | fromObjWithDefault, we test using the Maybe monad and an integer
502
-- value.
503
prop_Utils_fromObjWithDefault def_value random_key =
504
  -- a missing key will be returned with the default
505
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
506
  -- a found key will be returned as is, not with default
507
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
508
       random_key (def_value+1) == Just def_value
509
    where _types = def_value :: Integer
510

    
511
-- | Test that functional if' behaves like the syntactic sugar if.
512
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
513
prop_Utils_if'if cnd a b =
514
  Utils.if' cnd a b ==? if cnd then a else b
515

    
516
-- | Test basic select functionality
517
prop_Utils_select :: Int      -- ^ Default result
518
                  -> [Int]    -- ^ List of False values
519
                  -> [Int]    -- ^ List of True values
520
                  -> Gen Prop -- ^ Test result
521
prop_Utils_select def lst1 lst2 =
522
  Utils.select def (flist ++ tlist) ==? expectedresult
523
    where expectedresult = Utils.if' (null lst2) def (head lst2)
524
          flist = zip (repeat False) lst1
525
          tlist = zip (repeat True)  lst2
526

    
527
-- | Test basic select functionality with undefined default
528
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
529
                         -> NonEmptyList Int -- ^ List of True values
530
                         -> Gen Prop         -- ^ Test result
531
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
532
  Utils.select undefined (flist ++ tlist) ==? head lst2
533
    where flist = zip (repeat False) lst1
534
          tlist = zip (repeat True)  lst2
535

    
536
-- | Test basic select functionality with undefined list values
537
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
538
                         -> NonEmptyList Int -- ^ List of True values
539
                         -> Gen Prop         -- ^ Test result
540
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
541
  Utils.select undefined cndlist ==? head lst2
542
    where flist = zip (repeat False) lst1
543
          tlist = zip (repeat True)  lst2
544
          cndlist = flist ++ tlist ++ [undefined]
545

    
546
prop_Utils_parseUnit (NonNegative n) =
547
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
548
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
549
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
550
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
551
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
552
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
553
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
554
  printTestCase "Internal error/overflow?"
555
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
556
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
557
  where _types = (n::Int)
558
        n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
559
        n_gb = n_mb * 1000
560
        n_tb = n_gb * 1000
561

    
562
-- | Test list for the Utils module.
563
testSuite "Utils"
564
            [ 'prop_Utils_commaJoinSplit
565
            , 'prop_Utils_commaSplitJoin
566
            , 'prop_Utils_fromObjWithDefault
567
            , 'prop_Utils_if'if
568
            , 'prop_Utils_select
569
            , 'prop_Utils_select_undefd
570
            , 'prop_Utils_select_undefv
571
            , 'prop_Utils_parseUnit
572
            ]
573

    
574
-- ** PeerMap tests
575

    
576
-- | Make sure add is idempotent.
577
prop_PeerMap_addIdempotent pmap key em =
578
  fn puniq ==? fn (fn puniq)
579
    where _types = (pmap::PeerMap.PeerMap,
580
                    key::PeerMap.Key, em::PeerMap.Elem)
581
          fn = PeerMap.add key em
582
          puniq = PeerMap.accumArray const pmap
583

    
584
-- | Make sure remove is idempotent.
585
prop_PeerMap_removeIdempotent pmap key =
586
  fn puniq ==? fn (fn puniq)
587
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
588
          fn = PeerMap.remove key
589
          puniq = PeerMap.accumArray const pmap
590

    
591
-- | Make sure a missing item returns 0.
592
prop_PeerMap_findMissing pmap key =
593
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
594
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
595
          puniq = PeerMap.accumArray const pmap
596

    
597
-- | Make sure an added item is found.
598
prop_PeerMap_addFind pmap key em =
599
  PeerMap.find key (PeerMap.add key em puniq) ==? em
600
    where _types = (pmap::PeerMap.PeerMap,
601
                    key::PeerMap.Key, em::PeerMap.Elem)
602
          puniq = PeerMap.accumArray const pmap
603

    
604
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
605
prop_PeerMap_maxElem pmap =
606
  PeerMap.maxElem puniq ==? if null puniq then 0
607
                              else (maximum . snd . unzip) puniq
608
    where _types = pmap::PeerMap.PeerMap
609
          puniq = PeerMap.accumArray const pmap
610

    
611
-- | List of tests for the PeerMap module.
612
testSuite "PeerMap"
613
            [ 'prop_PeerMap_addIdempotent
614
            , 'prop_PeerMap_removeIdempotent
615
            , 'prop_PeerMap_maxElem
616
            , 'prop_PeerMap_addFind
617
            , 'prop_PeerMap_findMissing
618
            ]
619

    
620
-- ** Container tests
621

    
622
-- we silence the following due to hlint bug fixed in later versions
623
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
624
prop_Container_addTwo cdata i1 i2 =
625
  fn i1 i2 cont == fn i2 i1 cont &&
626
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
627
    where _types = (cdata::[Int],
628
                    i1::Int, i2::Int)
629
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
630
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
631

    
632
prop_Container_nameOf node =
633
  let nl = makeSmallCluster node 1
634
      fnode = head (Container.elems nl)
635
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
636

    
637
-- | We test that in a cluster, given a random node, we can find it by
638
-- its name and alias, as long as all names and aliases are unique,
639
-- and that we fail to find a non-existing name.
640
prop_Container_findByName node =
641
  forAll (choose (1, 20)) $ \ cnt ->
642
  forAll (choose (0, cnt - 1)) $ \ fidx ->
643
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
644
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
645
  let names = zip (take cnt allnames) (drop cnt allnames)
646
      nl = makeSmallCluster node cnt
647
      nodes = Container.elems nl
648
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
649
                                             nn { Node.name = name,
650
                                                  Node.alias = alias }))
651
               $ zip names nodes
652
      nl' = Container.fromList nodes'
653
      target = snd (nodes' !! fidx)
654
  in Container.findByName nl' (Node.name target) == Just target &&
655
     Container.findByName nl' (Node.alias target) == Just target &&
656
     isNothing (Container.findByName nl' othername)
657

    
658
testSuite "Container"
659
            [ 'prop_Container_addTwo
660
            , 'prop_Container_nameOf
661
            , 'prop_Container_findByName
662
            ]
663

    
664
-- ** Instance tests
665

    
666
-- Simple instance tests, we only have setter/getters
667

    
668
prop_Instance_creat inst =
669
  Instance.name inst ==? Instance.alias inst
670

    
671
prop_Instance_setIdx inst idx =
672
  Instance.idx (Instance.setIdx inst idx) ==? idx
673
    where _types = (inst::Instance.Instance, idx::Types.Idx)
674

    
675
prop_Instance_setName inst name =
676
  Instance.name newinst == name &&
677
  Instance.alias newinst == name
678
    where _types = (inst::Instance.Instance, name::String)
679
          newinst = Instance.setName inst name
680

    
681
prop_Instance_setAlias inst name =
682
  Instance.name newinst == Instance.name inst &&
683
  Instance.alias newinst == name
684
    where _types = (inst::Instance.Instance, name::String)
685
          newinst = Instance.setAlias inst name
686

    
687
prop_Instance_setPri inst pdx =
688
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
689
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
690

    
691
prop_Instance_setSec inst sdx =
692
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
693
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
694

    
695
prop_Instance_setBoth inst pdx sdx =
696
  Instance.pNode si == pdx && Instance.sNode si == sdx
697
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
698
          si = Instance.setBoth inst pdx sdx
699

    
700
prop_Instance_shrinkMG inst =
701
  Instance.mem inst >= 2 * Types.unitMem ==>
702
    case Instance.shrinkByType inst Types.FailMem of
703
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
704
      _ -> False
705

    
706
prop_Instance_shrinkMF inst =
707
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
708
    let inst' = inst { Instance.mem = mem}
709
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
710

    
711
prop_Instance_shrinkCG inst =
712
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
713
    case Instance.shrinkByType inst Types.FailCPU of
714
      Types.Ok inst' ->
715
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
716
      _ -> False
717

    
718
prop_Instance_shrinkCF inst =
719
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
720
    let inst' = inst { Instance.vcpus = vcpus }
721
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
722

    
723
prop_Instance_shrinkDG inst =
724
  Instance.dsk inst >= 2 * Types.unitDsk ==>
725
    case Instance.shrinkByType inst Types.FailDisk of
726
      Types.Ok inst' ->
727
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
728
      _ -> False
729

    
730
prop_Instance_shrinkDF inst =
731
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
732
    let inst' = inst { Instance.dsk = dsk }
733
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
734

    
735
prop_Instance_setMovable inst m =
736
  Instance.movable inst' ==? m
737
    where inst' = Instance.setMovable inst m
738

    
739
testSuite "Instance"
740
            [ 'prop_Instance_creat
741
            , 'prop_Instance_setIdx
742
            , 'prop_Instance_setName
743
            , 'prop_Instance_setAlias
744
            , 'prop_Instance_setPri
745
            , 'prop_Instance_setSec
746
            , 'prop_Instance_setBoth
747
            , 'prop_Instance_shrinkMG
748
            , 'prop_Instance_shrinkMF
749
            , 'prop_Instance_shrinkCG
750
            , 'prop_Instance_shrinkCF
751
            , 'prop_Instance_shrinkDG
752
            , 'prop_Instance_shrinkDF
753
            , 'prop_Instance_setMovable
754
            ]
755

    
756
-- ** Backends
757

    
758
-- *** Text backend tests
759

    
760
-- Instance text loader tests
761

    
762
prop_Text_Load_Instance name mem dsk vcpus status
763
                        (NonEmpty pnode) snode
764
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
765
  pnode /= snode && pdx /= sdx ==>
766
  let vcpus_s = show vcpus
767
      dsk_s = show dsk
768
      mem_s = show mem
769
      su_s = show su
770
      status_s = Types.instanceStatusToRaw status
771
      ndx = if null snode
772
              then [(pnode, pdx)]
773
              else [(pnode, pdx), (snode, sdx)]
774
      nl = Data.Map.fromList ndx
775
      tags = ""
776
      sbal = if autobal then "Y" else "N"
777
      sdt = Types.diskTemplateToRaw dt
778
      inst = Text.loadInst nl
779
             [name, mem_s, dsk_s, vcpus_s, status_s,
780
              sbal, pnode, snode, sdt, tags, su_s]
781
      fail1 = Text.loadInst nl
782
              [name, mem_s, dsk_s, vcpus_s, status_s,
783
               sbal, pnode, pnode, tags]
784
      _types = ( name::String, mem::Int, dsk::Int
785
               , vcpus::Int, status::Types.InstanceStatus
786
               , snode::String
787
               , autobal::Bool)
788
  in case inst of
789
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
790
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
791
                                        \ loading the instance" $
792
               Instance.name i == name &&
793
               Instance.vcpus i == vcpus &&
794
               Instance.mem i == mem &&
795
               Instance.pNode i == pdx &&
796
               Instance.sNode i == (if null snode
797
                                      then Node.noSecondary
798
                                      else sdx) &&
799
               Instance.autoBalance i == autobal &&
800
               Instance.spindleUsage i == su &&
801
               Types.isBad fail1
802

    
803
prop_Text_Load_InstanceFail ktn fields =
804
  length fields /= 10 && length fields /= 11 ==>
805
    case Text.loadInst nl fields of
806
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
807
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
808
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
809
    where nl = Data.Map.fromList ktn
810

    
811
prop_Text_Load_Node name tm nm fm td fd tc fo =
812
  let conv v = if v < 0
813
                 then "?"
814
                 else show v
815
      tm_s = conv tm
816
      nm_s = conv nm
817
      fm_s = conv fm
818
      td_s = conv td
819
      fd_s = conv fd
820
      tc_s = conv tc
821
      fo_s = if fo
822
               then "Y"
823
               else "N"
824
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
825
      gid = Group.uuid defGroup
826
  in case Text.loadNode defGroupAssoc
827
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
828
       Nothing -> False
829
       Just (name', node) ->
830
         if fo || any_broken
831
           then Node.offline node
832
           else Node.name node == name' && name' == name &&
833
                Node.alias node == name &&
834
                Node.tMem node == fromIntegral tm &&
835
                Node.nMem node == nm &&
836
                Node.fMem node == fm &&
837
                Node.tDsk node == fromIntegral td &&
838
                Node.fDsk node == fd &&
839
                Node.tCpu node == fromIntegral tc
840

    
841
prop_Text_Load_NodeFail fields =
842
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
843

    
844
prop_Text_NodeLSIdempotent node =
845
  (Text.loadNode defGroupAssoc.
846
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
847
  Just (Node.name n, n)
848
    -- override failN1 to what loadNode returns by default
849
    where n = Node.setPolicy Types.defIPolicy $
850
              node { Node.failN1 = True, Node.offline = False }
851

    
852
prop_Text_ISpecIdempotent ispec =
853
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
854
       Text.serializeISpec $ ispec of
855
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
856
    Types.Ok ispec' -> ispec ==? ispec'
857

    
858
prop_Text_IPolicyIdempotent ipol =
859
  case Text.loadIPolicy . Utils.sepSplit '|' $
860
       Text.serializeIPolicy owner ipol of
861
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
862
    Types.Ok res -> (owner, ipol) ==? res
863
  where owner = "dummy"
864

    
865
-- | This property, while being in the text tests, does more than just
866
-- test end-to-end the serialisation and loading back workflow; it
867
-- also tests the Loader.mergeData and the actuall
868
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
869
-- allocations, not for the business logic). As such, it's a quite
870
-- complex and slow test, and that's the reason we restrict it to
871
-- small cluster sizes.
872
prop_Text_CreateSerialise =
873
  forAll genTags $ \ctags ->
874
  forAll (choose (1, 20)) $ \maxiter ->
875
  forAll (choose (2, 10)) $ \count ->
876
  forAll genOnlineNode $ \node ->
877
  forAll (genInstanceSmallerThanNode node) $ \inst ->
878
  let nl = makeSmallCluster node count
879
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
880
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
881
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
882
     of
883
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
884
       Types.Ok (_, _, _, [], _) -> printTestCase
885
                                    "Failed to allocate: no allocations" False
886
       Types.Ok (_, nl', il', _, _) ->
887
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
888
                     Types.defIPolicy
889
             saved = Text.serializeCluster cdata
890
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
891
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
892
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
893
                ctags ==? ctags2 .&&.
894
                Types.defIPolicy ==? cpol2 .&&.
895
                il' ==? il2 .&&.
896
                defGroupList ==? gl2 .&&.
897
                nl' ==? nl2
898

    
899
testSuite "Text"
900
            [ 'prop_Text_Load_Instance
901
            , 'prop_Text_Load_InstanceFail
902
            , 'prop_Text_Load_Node
903
            , 'prop_Text_Load_NodeFail
904
            , 'prop_Text_NodeLSIdempotent
905
            , 'prop_Text_ISpecIdempotent
906
            , 'prop_Text_IPolicyIdempotent
907
            , 'prop_Text_CreateSerialise
908
            ]
909

    
910
-- *** Simu backend
911

    
912
-- | Generates a tuple of specs for simulation.
913
genSimuSpec :: Gen (String, Int, Int, Int, Int)
914
genSimuSpec = do
915
  pol <- elements [C.allocPolicyPreferred,
916
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
917
                  "p", "a", "u"]
918
 -- should be reasonable (nodes/group), bigger values only complicate
919
 -- the display of failed tests, and we don't care (in this particular
920
 -- test) about big node groups
921
  nodes <- choose (0, 20)
922
  dsk <- choose (0, maxDsk)
923
  mem <- choose (0, maxMem)
924
  cpu <- choose (0, maxCpu)
925
  return (pol, nodes, dsk, mem, cpu)
926

    
927
-- | Checks that given a set of corrects specs, we can load them
928
-- successfully, and that at high-level the values look right.
929
prop_SimuLoad =
930
  forAll (choose (0, 10)) $ \ngroups ->
931
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
932
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
933
                                          p n d m c::String) specs
934
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
935
      mdc_in = concatMap (\(_, n, d, m, c) ->
936
                            replicate n (fromIntegral m, fromIntegral d,
937
                                         fromIntegral c,
938
                                         fromIntegral m, fromIntegral d)) specs
939
  in case Simu.parseData strspecs of
940
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
941
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
942
         let nodes = map snd $ IntMap.toAscList nl
943
             nidx = map Node.idx nodes
944
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
945
                                   Node.fMem n, Node.fDsk n)) nodes
946
         in
947
         Container.size gl ==? ngroups .&&.
948
         Container.size nl ==? totnodes .&&.
949
         Container.size il ==? 0 .&&.
950
         length tags ==? 0 .&&.
951
         ipol ==? Types.defIPolicy .&&.
952
         nidx ==? [1..totnodes] .&&.
953
         mdc_in ==? mdc_out .&&.
954
         map Group.iPolicy (Container.elems gl) ==?
955
             replicate ngroups Types.defIPolicy
956

    
957
testSuite "Simu"
958
            [ 'prop_SimuLoad
959
            ]
960

    
961
-- ** Node tests
962

    
963
prop_Node_setAlias node name =
964
  Node.name newnode == Node.name node &&
965
  Node.alias newnode == name
966
    where _types = (node::Node.Node, name::String)
967
          newnode = Node.setAlias node name
968

    
969
prop_Node_setOffline node status =
970
  Node.offline newnode ==? status
971
    where newnode = Node.setOffline node status
972

    
973
prop_Node_setXmem node xm =
974
  Node.xMem newnode ==? xm
975
    where newnode = Node.setXmem node xm
976

    
977
prop_Node_setMcpu node mc =
978
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
979
    where newnode = Node.setMcpu node mc
980

    
981
-- | Check that an instance add with too high memory or disk will be
982
-- rejected.
983
prop_Node_addPriFM node inst =
984
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
985
  not (Instance.isOffline inst) ==>
986
  case Node.addPri node inst'' of
987
    Types.OpFail Types.FailMem -> True
988
    _ -> False
989
  where _types = (node::Node.Node, inst::Instance.Instance)
990
        inst' = setInstanceSmallerThanNode node inst
991
        inst'' = inst' { Instance.mem = Instance.mem inst }
992

    
993
prop_Node_addPriFD node inst =
994
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
995
    case Node.addPri node inst'' of
996
      Types.OpFail Types.FailDisk -> True
997
      _ -> False
998
    where _types = (node::Node.Node, inst::Instance.Instance)
999
          inst' = setInstanceSmallerThanNode node inst
1000
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
1001

    
1002
prop_Node_addPriFC =
1003
  forAll (choose (1, maxCpu)) $ \extra ->
1004
  forAll genOnlineNode $ \node ->
1005
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1006
  let inst' = setInstanceSmallerThanNode node inst
1007
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1008
  in case Node.addPri node inst'' of
1009
       Types.OpFail Types.FailCPU -> property True
1010
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1011

    
1012
-- | Check that an instance add with too high memory or disk will be
1013
-- rejected.
1014
prop_Node_addSec node inst pdx =
1015
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1016
    not (Instance.isOffline inst)) ||
1017
   Instance.dsk inst >= Node.fDsk node) &&
1018
  not (Node.failN1 node) ==>
1019
      isFailure (Node.addSec node inst pdx)
1020
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
1021

    
1022
-- | Check that an offline instance with reasonable disk size but
1023
-- extra mem/cpu can always be added.
1024
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1025
  forAll genOnlineNode $ \node ->
1026
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1027
  let inst' = inst { Instance.runSt = Types.AdminOffline
1028
                   , Instance.mem = Node.availMem node + extra_mem
1029
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1030
  in case Node.addPri node inst' of
1031
       Types.OpGood _ -> property True
1032
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1033

    
1034
-- | Check that an offline instance with reasonable disk size but
1035
-- extra mem/cpu can always be added.
1036
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1037
  forAll genOnlineNode $ \node ->
1038
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1039
  let inst' = inst { Instance.runSt = Types.AdminOffline
1040
                   , Instance.mem = Node.availMem node + extra_mem
1041
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1042
                   , Instance.diskTemplate = Types.DTDrbd8 }
1043
  in case Node.addSec node inst' pdx of
1044
       Types.OpGood _ -> property True
1045
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1046

    
1047
-- | Checks for memory reservation changes.
1048
prop_Node_rMem inst =
1049
  not (Instance.isOffline inst) ==>
1050
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1051
  -- ab = auto_balance, nb = non-auto_balance
1052
  -- we use -1 as the primary node of the instance
1053
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1054
                   , Instance.diskTemplate = Types.DTDrbd8 }
1055
      inst_ab = setInstanceSmallerThanNode node inst'
1056
      inst_nb = inst_ab { Instance.autoBalance = False }
1057
      -- now we have the two instances, identical except the
1058
      -- autoBalance attribute
1059
      orig_rmem = Node.rMem node
1060
      inst_idx = Instance.idx inst_ab
1061
      node_add_ab = Node.addSec node inst_ab (-1)
1062
      node_add_nb = Node.addSec node inst_nb (-1)
1063
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1064
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1065
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1066
       (Types.OpGood a_ab, Types.OpGood a_nb,
1067
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1068
         printTestCase "Consistency checks failed" $
1069
           Node.rMem a_ab >  orig_rmem &&
1070
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1071
           Node.rMem a_nb == orig_rmem &&
1072
           Node.rMem d_ab == orig_rmem &&
1073
           Node.rMem d_nb == orig_rmem &&
1074
           -- this is not related to rMem, but as good a place to
1075
           -- test as any
1076
           inst_idx `elem` Node.sList a_ab &&
1077
           inst_idx `notElem` Node.sList d_ab
1078
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1079

    
1080
-- | Check mdsk setting.
1081
prop_Node_setMdsk node mx =
1082
  Node.loDsk node' >= 0 &&
1083
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1084
  Node.availDisk node' >= 0 &&
1085
  Node.availDisk node' <= Node.fDsk node' &&
1086
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1087
  Node.mDsk node' == mx'
1088
    where _types = (node::Node.Node, mx::SmallRatio)
1089
          node' = Node.setMdsk node mx'
1090
          SmallRatio mx' = mx
1091

    
1092
-- Check tag maps
1093
prop_Node_tagMaps_idempotent =
1094
  forAll genTags $ \tags ->
1095
  Node.delTags (Node.addTags m tags) tags ==? m
1096
    where m = Data.Map.empty
1097

    
1098
prop_Node_tagMaps_reject =
1099
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1100
  let m = Node.addTags Data.Map.empty tags
1101
  in all (\t -> Node.rejectAddTags m [t]) tags
1102

    
1103
prop_Node_showField node =
1104
  forAll (elements Node.defaultFields) $ \ field ->
1105
  fst (Node.showHeader field) /= Types.unknownField &&
1106
  Node.showField node field /= Types.unknownField
1107

    
1108
prop_Node_computeGroups nodes =
1109
  let ng = Node.computeGroups nodes
1110
      onlyuuid = map fst ng
1111
  in length nodes == sum (map (length . snd) ng) &&
1112
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1113
     length (nub onlyuuid) == length onlyuuid &&
1114
     (null nodes || not (null ng))
1115

    
1116
-- Check idempotence of add/remove operations
1117
prop_Node_addPri_idempotent =
1118
  forAll genOnlineNode $ \node ->
1119
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1120
  case Node.addPri node inst of
1121
    Types.OpGood node' -> Node.removePri node' inst ==? node
1122
    _ -> failTest "Can't add instance"
1123

    
1124
prop_Node_addSec_idempotent =
1125
  forAll genOnlineNode $ \node ->
1126
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1127
  let pdx = Node.idx node + 1
1128
      inst' = Instance.setPri inst pdx
1129
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1130
  in case Node.addSec node inst'' pdx of
1131
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1132
       _ -> failTest "Can't add instance"
1133

    
1134
testSuite "Node"
1135
            [ 'prop_Node_setAlias
1136
            , 'prop_Node_setOffline
1137
            , 'prop_Node_setMcpu
1138
            , 'prop_Node_setXmem
1139
            , 'prop_Node_addPriFM
1140
            , 'prop_Node_addPriFD
1141
            , 'prop_Node_addPriFC
1142
            , 'prop_Node_addSec
1143
            , 'prop_Node_addOfflinePri
1144
            , 'prop_Node_addOfflineSec
1145
            , 'prop_Node_rMem
1146
            , 'prop_Node_setMdsk
1147
            , 'prop_Node_tagMaps_idempotent
1148
            , 'prop_Node_tagMaps_reject
1149
            , 'prop_Node_showField
1150
            , 'prop_Node_computeGroups
1151
            , 'prop_Node_addPri_idempotent
1152
            , 'prop_Node_addSec_idempotent
1153
            ]
1154

    
1155
-- ** Cluster tests
1156

    
1157
-- | Check that the cluster score is close to zero for a homogeneous
1158
-- cluster.
1159
prop_Score_Zero node =
1160
  forAll (choose (1, 1024)) $ \count ->
1161
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1162
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1163
  let fn = Node.buildPeers node Container.empty
1164
      nlst = replicate count fn
1165
      score = Cluster.compCVNodes nlst
1166
  -- we can't say == 0 here as the floating point errors accumulate;
1167
  -- this should be much lower than the default score in CLI.hs
1168
  in score <= 1e-12
1169

    
1170
-- | Check that cluster stats are sane.
1171
prop_CStats_sane =
1172
  forAll (choose (1, 1024)) $ \count ->
1173
  forAll genOnlineNode $ \node ->
1174
  let fn = Node.buildPeers node Container.empty
1175
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1176
      nl = Container.fromList nlst
1177
      cstats = Cluster.totalResources nl
1178
  in Cluster.csAdsk cstats >= 0 &&
1179
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1180

    
1181
-- | Check that one instance is allocated correctly, without
1182
-- rebalances needed.
1183
prop_ClusterAlloc_sane inst =
1184
  forAll (choose (5, 20)) $ \count ->
1185
  forAll genOnlineNode $ \node ->
1186
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1187
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1188
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1189
     Cluster.tryAlloc nl il inst' of
1190
       Types.Bad _ -> False
1191
       Types.Ok as ->
1192
         case Cluster.asSolution as of
1193
           Nothing -> False
1194
           Just (xnl, xi, _, cv) ->
1195
             let il' = Container.add (Instance.idx xi) xi il
1196
                 tbl = Cluster.Table xnl il' cv []
1197
             in not (canBalance tbl True True False)
1198

    
1199
-- | Checks that on a 2-5 node cluster, we can allocate a random
1200
-- instance spec via tiered allocation (whatever the original instance
1201
-- spec), on either one or two nodes. Furthermore, we test that
1202
-- computed allocation statistics are correct.
1203
prop_ClusterCanTieredAlloc inst =
1204
  forAll (choose (2, 5)) $ \count ->
1205
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1206
  let nl = makeSmallCluster node count
1207
      il = Container.empty
1208
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1209
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1210
  in case allocnodes >>= \allocnodes' ->
1211
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1212
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1213
       Types.Ok (_, nl', il', ixes, cstats) ->
1214
         let (ai_alloc, ai_pool, ai_unav) =
1215
               Cluster.computeAllocationDelta
1216
                (Cluster.totalResources nl)
1217
                (Cluster.totalResources nl')
1218
             all_nodes = Container.elems nl
1219
         in property (not (null ixes)) .&&.
1220
            IntMap.size il' ==? length ixes .&&.
1221
            length ixes ==? length cstats .&&.
1222
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1223
              sum (map Node.hiCpu all_nodes) .&&.
1224
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1225
              sum (map Node.tCpu all_nodes) .&&.
1226
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1227
              truncate (sum (map Node.tMem all_nodes)) .&&.
1228
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1229
              truncate (sum (map Node.tDsk all_nodes))
1230

    
1231
-- | Helper function to create a cluster with the given range of nodes
1232
-- and allocate an instance on it.
1233
genClusterAlloc count node inst =
1234
  let nl = makeSmallCluster node count
1235
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1236
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1237
     Cluster.tryAlloc nl Container.empty inst of
1238
       Types.Bad _ -> Types.Bad "Can't allocate"
1239
       Types.Ok as ->
1240
         case Cluster.asSolution as of
1241
           Nothing -> Types.Bad "Empty solution?"
1242
           Just (xnl, xi, _, _) ->
1243
             let xil = Container.add (Instance.idx xi) xi Container.empty
1244
             in Types.Ok (xnl, xil, xi)
1245

    
1246
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1247
-- we can also relocate it.
1248
prop_ClusterAllocRelocate =
1249
  forAll (choose (4, 8)) $ \count ->
1250
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1251
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1252
  case genClusterAlloc count node inst of
1253
    Types.Bad msg -> failTest msg
1254
    Types.Ok (nl, il, inst') ->
1255
      case IAlloc.processRelocate defGroupList nl il
1256
             (Instance.idx inst) 1
1257
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1258
                 then Instance.sNode
1259
                 else Instance.pNode) inst'] of
1260
        Types.Ok _ -> property True
1261
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1262

    
1263
-- | Helper property checker for the result of a nodeEvac or
1264
-- changeGroup operation.
1265
check_EvacMode grp inst result =
1266
  case result of
1267
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1268
    Types.Ok (_, _, es) ->
1269
      let moved = Cluster.esMoved es
1270
          failed = Cluster.esFailed es
1271
          opcodes = not . null $ Cluster.esOpCodes es
1272
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1273
         failmsg "'opcodes' is null" opcodes .&&.
1274
         case moved of
1275
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1276
                               .&&.
1277
                               failmsg "wrong target group"
1278
                                         (gdx == Group.idx grp)
1279
           v -> failmsg  ("invalid solution: " ++ show v) False
1280
  where failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1281
        idx = Instance.idx inst
1282

    
1283
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1284
-- we can also node-evacuate it.
1285
prop_ClusterAllocEvacuate =
1286
  forAll (choose (4, 8)) $ \count ->
1287
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1288
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1289
  case genClusterAlloc count node inst of
1290
    Types.Bad msg -> failTest msg
1291
    Types.Ok (nl, il, inst') ->
1292
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1293
                              Cluster.tryNodeEvac defGroupList nl il mode
1294
                                [Instance.idx inst']) .
1295
                              evacModeOptions . Types.templateMirrorType .
1296
                              Instance.diskTemplate $ inst'
1297

    
1298
-- | Checks that on a 4-8 node cluster with two node groups, once we
1299
-- allocate an instance on the first node group, we can also change
1300
-- its group.
1301
prop_ClusterAllocChangeGroup =
1302
  forAll (choose (4, 8)) $ \count ->
1303
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1304
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1305
  case genClusterAlloc count node inst of
1306
    Types.Bad msg -> failTest msg
1307
    Types.Ok (nl, il, inst') ->
1308
      -- we need to add a second node group and nodes to the cluster
1309
      let nl2 = Container.elems $ makeSmallCluster node count
1310
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1311
          maxndx = maximum . map Node.idx $ nl2
1312
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1313
                             , Node.idx = Node.idx n + maxndx }) nl2
1314
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1315
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1316
          nl' = IntMap.union nl nl4
1317
      in check_EvacMode grp2 inst' $
1318
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1319

    
1320
-- | Check that allocating multiple instances on a cluster, then
1321
-- adding an empty node, results in a valid rebalance.
1322
prop_ClusterAllocBalance =
1323
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1324
  forAll (choose (3, 5)) $ \count ->
1325
  not (Node.offline node) && not (Node.failN1 node) ==>
1326
  let nl = makeSmallCluster node count
1327
      (hnode, nl') = IntMap.deleteFindMax nl
1328
      il = Container.empty
1329
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1330
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1331
  in case allocnodes >>= \allocnodes' ->
1332
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1333
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1334
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1335
       Types.Ok (_, xnl, il', _, _) ->
1336
         let ynl = Container.add (Node.idx hnode) hnode xnl
1337
             cv = Cluster.compCV ynl
1338
             tbl = Cluster.Table ynl il' cv []
1339
         in printTestCase "Failed to rebalance" $
1340
            canBalance tbl True True False
1341

    
1342
-- | Checks consistency.
1343
prop_ClusterCheckConsistency node inst =
1344
  let nl = makeSmallCluster node 3
1345
      [node1, node2, node3] = Container.elems nl
1346
      node3' = node3 { Node.group = 1 }
1347
      nl' = Container.add (Node.idx node3') node3' nl
1348
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1349
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1350
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1351
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1352
  in null (ccheck [(0, inst1)]) &&
1353
     null (ccheck [(0, inst2)]) &&
1354
     (not . null $ ccheck [(0, inst3)])
1355

    
1356
-- | For now, we only test that we don't lose instances during the split.
1357
prop_ClusterSplitCluster node inst =
1358
  forAll (choose (0, 100)) $ \icnt ->
1359
  let nl = makeSmallCluster node 2
1360
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1361
                   (nl, Container.empty) [1..icnt]
1362
      gni = Cluster.splitCluster nl' il'
1363
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1364
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1365
                                 (Container.elems nl'')) gni
1366

    
1367
-- | Helper function to check if we can allocate an instance on a
1368
-- given node list.
1369
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1370
canAllocOn nl reqnodes inst =
1371
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1372
       Cluster.tryAlloc nl (Container.empty) inst of
1373
       Types.Bad _ -> False
1374
       Types.Ok as ->
1375
         case Cluster.asSolution as of
1376
           Nothing -> False
1377
           Just _ -> True
1378

    
1379
-- | Checks that allocation obeys minimum and maximum instance
1380
-- policies. The unittest generates a random node, duplicates it count
1381
-- times, and generates a random instance that can be allocated on
1382
-- this mini-cluster; it then checks that after applying a policy that
1383
-- the instance doesn't fits, the allocation fails.
1384
prop_ClusterAllocPolicy node =
1385
  -- rqn is the required nodes (1 or 2)
1386
  forAll (choose (1, 2)) $ \rqn ->
1387
  forAll (choose (5, 20)) $ \count ->
1388
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1389
         $ \inst ->
1390
  forAll (arbitrary `suchThat` (isFailure .
1391
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1392
  let node' = Node.setPolicy ipol node
1393
      nl = makeSmallCluster node' count
1394
  in not $ canAllocOn nl rqn inst
1395

    
1396
testSuite "Cluster"
1397
            [ 'prop_Score_Zero
1398
            , 'prop_CStats_sane
1399
            , 'prop_ClusterAlloc_sane
1400
            , 'prop_ClusterCanTieredAlloc
1401
            , 'prop_ClusterAllocRelocate
1402
            , 'prop_ClusterAllocEvacuate
1403
            , 'prop_ClusterAllocChangeGroup
1404
            , 'prop_ClusterAllocBalance
1405
            , 'prop_ClusterCheckConsistency
1406
            , 'prop_ClusterSplitCluster
1407
            , 'prop_ClusterAllocPolicy
1408
            ]
1409

    
1410
-- ** OpCodes tests
1411

    
1412
-- | Check that opcode serialization is idempotent.
1413
prop_OpCodes_serialization op =
1414
  case J.readJSON (J.showJSON op) of
1415
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1416
    J.Ok op' -> op ==? op'
1417
  where _types = op::OpCodes.OpCode
1418

    
1419
testSuite "OpCodes"
1420
            [ 'prop_OpCodes_serialization ]
1421

    
1422
-- ** Jobs tests
1423

    
1424
-- | Check that (queued) job\/opcode status serialization is idempotent.
1425
prop_OpStatus_serialization os =
1426
  case J.readJSON (J.showJSON os) of
1427
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1428
    J.Ok os' -> os ==? os'
1429
  where _types = os::Jobs.OpStatus
1430

    
1431
prop_JobStatus_serialization js =
1432
  case J.readJSON (J.showJSON js) of
1433
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1434
    J.Ok js' -> js ==? js'
1435
  where _types = js::Jobs.JobStatus
1436

    
1437
testSuite "Jobs"
1438
            [ 'prop_OpStatus_serialization
1439
            , 'prop_JobStatus_serialization
1440
            ]
1441

    
1442
-- ** Loader tests
1443

    
1444
prop_Loader_lookupNode ktn inst node =
1445
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1446
    where nl = Data.Map.fromList ktn
1447

    
1448
prop_Loader_lookupInstance kti inst =
1449
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1450
    where il = Data.Map.fromList kti
1451

    
1452
prop_Loader_assignIndices =
1453
  -- generate nodes with unique names
1454
  forAll (arbitrary `suchThat`
1455
          (\nodes ->
1456
             let names = map Node.name nodes
1457
             in length names == length (nub names))) $ \nodes ->
1458
  let (nassoc, kt) =
1459
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1460
  in Data.Map.size nassoc == length nodes &&
1461
     Container.size kt == length nodes &&
1462
     if not (null nodes)
1463
       then maximum (IntMap.keys kt) == length nodes - 1
1464
       else True
1465

    
1466
-- | Checks that the number of primary instances recorded on the nodes
1467
-- is zero.
1468
prop_Loader_mergeData ns =
1469
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1470
  in case Loader.mergeData [] [] [] []
1471
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1472
    Types.Bad _ -> False
1473
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1474
      let nodes = Container.elems nl
1475
          instances = Container.elems il
1476
      in (sum . map (length . Node.pList)) nodes == 0 &&
1477
         null instances
1478

    
1479
-- | Check that compareNameComponent on equal strings works.
1480
prop_Loader_compareNameComponent_equal :: String -> Bool
1481
prop_Loader_compareNameComponent_equal s =
1482
  Loader.compareNameComponent s s ==
1483
    Loader.LookupResult Loader.ExactMatch s
1484

    
1485
-- | Check that compareNameComponent on prefix strings works.
1486
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1487
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1488
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1489
    Loader.LookupResult Loader.PartialMatch s1
1490

    
1491
testSuite "Loader"
1492
            [ 'prop_Loader_lookupNode
1493
            , 'prop_Loader_lookupInstance
1494
            , 'prop_Loader_assignIndices
1495
            , 'prop_Loader_mergeData
1496
            , 'prop_Loader_compareNameComponent_equal
1497
            , 'prop_Loader_compareNameComponent_prefix
1498
            ]
1499

    
1500
-- ** Types tests
1501

    
1502
prop_Types_AllocPolicy_serialisation apol =
1503
  case J.readJSON (J.showJSON apol) of
1504
    J.Ok p -> p ==? apol
1505
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1506
      where _types = apol::Types.AllocPolicy
1507

    
1508
prop_Types_DiskTemplate_serialisation dt =
1509
  case J.readJSON (J.showJSON dt) of
1510
    J.Ok p -> p ==? dt
1511
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1512
      where _types = dt::Types.DiskTemplate
1513

    
1514
prop_Types_ISpec_serialisation ispec =
1515
  case J.readJSON (J.showJSON ispec) of
1516
    J.Ok p -> p ==? ispec
1517
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1518
      where _types = ispec::Types.ISpec
1519

    
1520
prop_Types_IPolicy_serialisation ipol =
1521
  case J.readJSON (J.showJSON ipol) of
1522
    J.Ok p -> p ==? ipol
1523
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1524
      where _types = ipol::Types.IPolicy
1525

    
1526
prop_Types_EvacMode_serialisation em =
1527
  case J.readJSON (J.showJSON em) of
1528
    J.Ok p -> p ==? em
1529
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1530
      where _types = em::Types.EvacMode
1531

    
1532
prop_Types_opToResult op =
1533
  case op of
1534
    Types.OpFail _ -> Types.isBad r
1535
    Types.OpGood v -> case r of
1536
                        Types.Bad _ -> False
1537
                        Types.Ok v' -> v == v'
1538
  where r = Types.opToResult op
1539
        _types = op::Types.OpResult Int
1540

    
1541
prop_Types_eitherToResult ei =
1542
  case ei of
1543
    Left _ -> Types.isBad r
1544
    Right v -> case r of
1545
                 Types.Bad _ -> False
1546
                 Types.Ok v' -> v == v'
1547
    where r = Types.eitherToResult ei
1548
          _types = ei::Either String Int
1549

    
1550
testSuite "Types"
1551
            [ 'prop_Types_AllocPolicy_serialisation
1552
            , 'prop_Types_DiskTemplate_serialisation
1553
            , 'prop_Types_ISpec_serialisation
1554
            , 'prop_Types_IPolicy_serialisation
1555
            , 'prop_Types_EvacMode_serialisation
1556
            , 'prop_Types_opToResult
1557
            , 'prop_Types_eitherToResult
1558
            ]
1559

    
1560
-- ** CLI tests
1561

    
1562
-- | Test correct parsing.
1563
prop_CLI_parseISpec descr dsk mem cpu =
1564
  let str = printf "%d,%d,%d" dsk mem cpu
1565
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1566

    
1567
-- | Test parsing failure due to wrong section count.
1568
prop_CLI_parseISpecFail descr =
1569
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1570
  forAll (replicateM nelems arbitrary) $ \values ->
1571
  let str = intercalate "," $ map show (values::[Int])
1572
  in case CLI.parseISpecString descr str of
1573
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1574
       _ -> property True
1575

    
1576
-- | Test parseYesNo.
1577
prop_CLI_parseYesNo def testval val =
1578
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1579
  if testval
1580
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1581
    else let result = CLI.parseYesNo def (Just actual_val)
1582
         in if actual_val `elem` ["yes", "no"]
1583
              then result ==? Types.Ok (actual_val == "yes")
1584
              else property $ Types.isBad result
1585

    
1586
-- | Helper to check for correct parsing of string arg.
1587
checkStringArg val (opt, fn) =
1588
  let GetOpt.Option _ longs _ _ = opt
1589
  in case longs of
1590
       [] -> failTest "no long options?"
1591
       cmdarg:_ ->
1592
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1593
           Left e -> failTest $ "Failed to parse option: " ++ show e
1594
           Right (options, _) -> fn options ==? Just val
1595

    
1596
-- | Test a few string arguments.
1597
prop_CLI_StringArg argument =
1598
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1599
             , (CLI.oDynuFile,      CLI.optDynuFile)
1600
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1601
             , (CLI.oReplay,        CLI.optReplay)
1602
             , (CLI.oPrintCommands, CLI.optShowCmds)
1603
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1604
             ]
1605
  in conjoin $ map (checkStringArg argument) args
1606

    
1607
-- | Helper to test that a given option is accepted OK with quick exit.
1608
checkEarlyExit name options param =
1609
  case CLI.parseOptsInner [param] name options of
1610
    Left (code, _) -> if code == 0
1611
                          then property True
1612
                          else failTest $ "Program " ++ name ++
1613
                                 " returns invalid code " ++ show code ++
1614
                                 " for option " ++ param
1615
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1616
         param ++ " as early exit one"
1617

    
1618
-- | Test that all binaries support some common options. There is
1619
-- nothing actually random about this test...
1620
prop_CLI_stdopts =
1621
  let params = ["-h", "--help", "-V", "--version"]
1622
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1623
      -- apply checkEarlyExit across the cartesian product of params and opts
1624
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1625

    
1626
testSuite "CLI"
1627
          [ 'prop_CLI_parseISpec
1628
          , 'prop_CLI_parseISpecFail
1629
          , 'prop_CLI_parseYesNo
1630
          , 'prop_CLI_StringArg
1631
          , 'prop_CLI_stdopts
1632
          ]