Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 52cc1370

History | View | Annotate | Download (61.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
  ) 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
                                       }
120
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
121
                                       , Types.iSpecCpuCount   = maxBound
122
                                       , Types.iSpecDiskSize   = maxBound
123
                                       , Types.iSpecDiskCount  = C.maxDisks
124
                                       , Types.iSpecNicCount   = C.maxNics
125
                                       }
126
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
127
                                       , Types.iSpecCpuCount   = Types.unitCpu
128
                                       , Types.iSpecDiskSize   = Types.unitDsk
129
                                       , Types.iSpecDiskCount  = 1
130
                                       , Types.iSpecNicCount   = 1
131
                                       }
132
  , Types.iPolicyDiskTemplates = [Types.DTDrbd8, Types.DTPlain]
133
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
134
                                          -- enough to not impact us
135
  , Types.iPolicySpindleRatio = maxSpindleRatio
136
  }
137

    
138

    
139
defGroup :: Group.Group
140
defGroup = flip Group.setIdx 0 $
141
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
142
                  nullIPolicy
143

    
144
defGroupList :: Group.List
145
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
146

    
147
defGroupAssoc :: Data.Map.Map String Types.Gdx
148
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
149

    
150
-- * Helper functions
151

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

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

    
164
-- | Show a message and fail the test.
165
failTest :: String -> Property
166
failTest msg = printTestCase msg False
167

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

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

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

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

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

    
206
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
207
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
208

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

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

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

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

    
246
-- * Arbitrary instances
247

    
248
-- | Defines a DNS name.
249
newtype DNSChar = DNSChar { dnsGetChar::Char }
250

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

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

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

    
270
-- | Defines a tag type.
271
newtype TagChar = TagChar { tagGetChar :: Char }
272

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

    
278
instance Arbitrary TagChar where
279
  arbitrary = do
280
    c <- elements tagChar
281
    return (TagChar c)
282

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

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

    
302
instance Arbitrary Types.InstanceStatus where
303
    arbitrary = elements [minBound..maxBound]
304

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

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

    
325
-- let's generate a random instance
326
instance Arbitrary Instance.Instance where
327
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
328

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

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

    
369
-- and a random node
370
instance Arbitrary Node.Node where
371
  arbitrary = genNode Nothing Nothing
372

    
373
-- replace disks
374
instance Arbitrary OpCodes.ReplaceDisksMode where
375
  arbitrary = elements [minBound..maxBound]
376

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

    
398
instance Arbitrary Jobs.OpStatus where
399
  arbitrary = elements [minBound..maxBound]
400

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

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

    
410
instance Arbitrary Types.AllocPolicy where
411
  arbitrary = elements [minBound..maxBound]
412

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

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

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

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

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

    
442
-- | Generates an ispec bigger than the given one.
443
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
444
genBiggerISpec imin = do
445
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
446
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
447
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
448
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
449
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
450
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
451
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
452
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
453
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
454
                     , Types.iSpecNicCount   = fromIntegral nic_c
455
                     }
456

    
457
instance Arbitrary Types.IPolicy where
458
  arbitrary = do
459
    imin <- arbitrary
460
    istd <- genBiggerISpec imin
461
    imax <- genBiggerISpec istd
462
    num_tmpl <- choose (0, length allDiskTemplates)
463
    dts  <- genUniquesList num_tmpl
464
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
465
    spindle_ratio <- choose (1.0, maxSpindleRatio)
466
    return Types.IPolicy { Types.iPolicyMinSpec = imin
467
                         , Types.iPolicyStdSpec = istd
468
                         , Types.iPolicyMaxSpec = imax
469
                         , Types.iPolicyDiskTemplates = dts
470
                         , Types.iPolicyVcpuRatio = vcpu_ratio
471
                         , Types.iPolicySpindleRatio = spindle_ratio
472
                         }
473

    
474
-- * Actual tests
475

    
476
-- ** Utils tests
477

    
478
-- | Helper to generate a small string that doesn't contain commas.
479
genNonCommaString = do
480
  size <- choose (0, 20) -- arbitrary max size
481
  vectorOf size (arbitrary `suchThat` ((/=) ','))
482

    
483
-- | If the list is not just an empty element, and if the elements do
484
-- not contain commas, then join+split should be idempotent.
485
prop_Utils_commaJoinSplit =
486
  forAll (choose (0, 20)) $ \llen ->
487
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
488
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
489

    
490
-- | Split and join should always be idempotent.
491
prop_Utils_commaSplitJoin s =
492
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
493

    
494
-- | fromObjWithDefault, we test using the Maybe monad and an integer
495
-- value.
496
prop_Utils_fromObjWithDefault def_value random_key =
497
  -- a missing key will be returned with the default
498
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
499
  -- a found key will be returned as is, not with default
500
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
501
       random_key (def_value+1) == Just def_value
502
    where _types = def_value :: Integer
503

    
504
-- | Test that functional if' behaves like the syntactic sugar if.
505
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
506
prop_Utils_if'if cnd a b =
507
  Utils.if' cnd a b ==? if cnd then a else b
508

    
509
-- | Test basic select functionality
510
prop_Utils_select :: Int      -- ^ Default result
511
                  -> [Int]    -- ^ List of False values
512
                  -> [Int]    -- ^ List of True values
513
                  -> Gen Prop -- ^ Test result
514
prop_Utils_select def lst1 lst2 =
515
  Utils.select def (flist ++ tlist) ==? expectedresult
516
    where expectedresult = Utils.if' (null lst2) def (head lst2)
517
          flist = zip (repeat False) lst1
518
          tlist = zip (repeat True)  lst2
519

    
520
-- | Test basic select functionality with undefined default
521
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
522
                         -> NonEmptyList Int -- ^ List of True values
523
                         -> Gen Prop         -- ^ Test result
524
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
525
  Utils.select undefined (flist ++ tlist) ==? head lst2
526
    where flist = zip (repeat False) lst1
527
          tlist = zip (repeat True)  lst2
528

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

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

    
555
-- | Test list for the Utils module.
556
testSuite "Utils"
557
            [ 'prop_Utils_commaJoinSplit
558
            , 'prop_Utils_commaSplitJoin
559
            , 'prop_Utils_fromObjWithDefault
560
            , 'prop_Utils_if'if
561
            , 'prop_Utils_select
562
            , 'prop_Utils_select_undefd
563
            , 'prop_Utils_select_undefv
564
            , 'prop_Utils_parseUnit
565
            ]
566

    
567
-- ** PeerMap tests
568

    
569
-- | Make sure add is idempotent.
570
prop_PeerMap_addIdempotent pmap key em =
571
  fn puniq ==? fn (fn puniq)
572
    where _types = (pmap::PeerMap.PeerMap,
573
                    key::PeerMap.Key, em::PeerMap.Elem)
574
          fn = PeerMap.add key em
575
          puniq = PeerMap.accumArray const pmap
576

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

    
584
-- | Make sure a missing item returns 0.
585
prop_PeerMap_findMissing pmap key =
586
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
587
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
588
          puniq = PeerMap.accumArray const pmap
589

    
590
-- | Make sure an added item is found.
591
prop_PeerMap_addFind pmap key em =
592
  PeerMap.find key (PeerMap.add key em puniq) ==? em
593
    where _types = (pmap::PeerMap.PeerMap,
594
                    key::PeerMap.Key, em::PeerMap.Elem)
595
          puniq = PeerMap.accumArray const pmap
596

    
597
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
598
prop_PeerMap_maxElem pmap =
599
  PeerMap.maxElem puniq ==? if null puniq then 0
600
                              else (maximum . snd . unzip) puniq
601
    where _types = pmap::PeerMap.PeerMap
602
          puniq = PeerMap.accumArray const pmap
603

    
604
-- | List of tests for the PeerMap module.
605
testSuite "PeerMap"
606
            [ 'prop_PeerMap_addIdempotent
607
            , 'prop_PeerMap_removeIdempotent
608
            , 'prop_PeerMap_maxElem
609
            , 'prop_PeerMap_addFind
610
            , 'prop_PeerMap_findMissing
611
            ]
612

    
613
-- ** Container tests
614

    
615
-- we silence the following due to hlint bug fixed in later versions
616
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
617
prop_Container_addTwo cdata i1 i2 =
618
  fn i1 i2 cont == fn i2 i1 cont &&
619
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
620
    where _types = (cdata::[Int],
621
                    i1::Int, i2::Int)
622
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
623
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
624

    
625
prop_Container_nameOf node =
626
  let nl = makeSmallCluster node 1
627
      fnode = head (Container.elems nl)
628
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
629

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

    
651
testSuite "Container"
652
            [ 'prop_Container_addTwo
653
            , 'prop_Container_nameOf
654
            , 'prop_Container_findByName
655
            ]
656

    
657
-- ** Instance tests
658

    
659
-- Simple instance tests, we only have setter/getters
660

    
661
prop_Instance_creat inst =
662
  Instance.name inst ==? Instance.alias inst
663

    
664
prop_Instance_setIdx inst idx =
665
  Instance.idx (Instance.setIdx inst idx) ==? idx
666
    where _types = (inst::Instance.Instance, idx::Types.Idx)
667

    
668
prop_Instance_setName inst name =
669
  Instance.name newinst == name &&
670
  Instance.alias newinst == name
671
    where _types = (inst::Instance.Instance, name::String)
672
          newinst = Instance.setName inst name
673

    
674
prop_Instance_setAlias inst name =
675
  Instance.name newinst == Instance.name inst &&
676
  Instance.alias newinst == name
677
    where _types = (inst::Instance.Instance, name::String)
678
          newinst = Instance.setAlias inst name
679

    
680
prop_Instance_setPri inst pdx =
681
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
682
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
683

    
684
prop_Instance_setSec inst sdx =
685
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
686
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
687

    
688
prop_Instance_setBoth inst pdx sdx =
689
  Instance.pNode si == pdx && Instance.sNode si == sdx
690
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
691
          si = Instance.setBoth inst pdx sdx
692

    
693
prop_Instance_shrinkMG inst =
694
  Instance.mem inst >= 2 * Types.unitMem ==>
695
    case Instance.shrinkByType inst Types.FailMem of
696
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
697
      _ -> False
698

    
699
prop_Instance_shrinkMF inst =
700
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
701
    let inst' = inst { Instance.mem = mem}
702
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
703

    
704
prop_Instance_shrinkCG inst =
705
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
706
    case Instance.shrinkByType inst Types.FailCPU of
707
      Types.Ok inst' ->
708
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
709
      _ -> False
710

    
711
prop_Instance_shrinkCF inst =
712
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
713
    let inst' = inst { Instance.vcpus = vcpus }
714
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
715

    
716
prop_Instance_shrinkDG inst =
717
  Instance.dsk inst >= 2 * Types.unitDsk ==>
718
    case Instance.shrinkByType inst Types.FailDisk of
719
      Types.Ok inst' ->
720
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
721
      _ -> False
722

    
723
prop_Instance_shrinkDF inst =
724
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
725
    let inst' = inst { Instance.dsk = dsk }
726
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
727

    
728
prop_Instance_setMovable inst m =
729
  Instance.movable inst' ==? m
730
    where inst' = Instance.setMovable inst m
731

    
732
testSuite "Instance"
733
            [ 'prop_Instance_creat
734
            , 'prop_Instance_setIdx
735
            , 'prop_Instance_setName
736
            , 'prop_Instance_setAlias
737
            , 'prop_Instance_setPri
738
            , 'prop_Instance_setSec
739
            , 'prop_Instance_setBoth
740
            , 'prop_Instance_shrinkMG
741
            , 'prop_Instance_shrinkMF
742
            , 'prop_Instance_shrinkCG
743
            , 'prop_Instance_shrinkCF
744
            , 'prop_Instance_shrinkDG
745
            , 'prop_Instance_shrinkDF
746
            , 'prop_Instance_setMovable
747
            ]
748

    
749
-- ** Backends
750

    
751
-- *** Text backend tests
752

    
753
-- Instance text loader tests
754

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

    
796
prop_Text_Load_InstanceFail ktn fields =
797
  length fields /= 10 && length fields /= 11 ==>
798
    case Text.loadInst nl fields of
799
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
800
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
801
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
802
    where nl = Data.Map.fromList ktn
803

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

    
834
prop_Text_Load_NodeFail fields =
835
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
836

    
837
prop_Text_NodeLSIdempotent node =
838
  (Text.loadNode defGroupAssoc.
839
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
840
  Just (Node.name n, n)
841
    -- override failN1 to what loadNode returns by default
842
    where n = Node.setPolicy Types.defIPolicy $
843
              node { Node.failN1 = True, Node.offline = False }
844

    
845
prop_Text_ISpecIdempotent ispec =
846
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
847
       Text.serializeISpec $ ispec of
848
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
849
    Types.Ok ispec' -> ispec ==? ispec'
850

    
851
prop_Text_IPolicyIdempotent ipol =
852
  case Text.loadIPolicy . Utils.sepSplit '|' $
853
       Text.serializeIPolicy owner ipol of
854
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
855
    Types.Ok res -> (owner, ipol) ==? res
856
  where owner = "dummy"
857

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

    
892
testSuite "Text"
893
            [ 'prop_Text_Load_Instance
894
            , 'prop_Text_Load_InstanceFail
895
            , 'prop_Text_Load_Node
896
            , 'prop_Text_Load_NodeFail
897
            , 'prop_Text_NodeLSIdempotent
898
            , 'prop_Text_ISpecIdempotent
899
            , 'prop_Text_IPolicyIdempotent
900
            , 'prop_Text_CreateSerialise
901
            ]
902

    
903
-- *** Simu backend
904

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

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

    
950
testSuite "Simu"
951
            [ 'prop_SimuLoad
952
            ]
953

    
954
-- ** Node tests
955

    
956
prop_Node_setAlias node name =
957
  Node.name newnode == Node.name node &&
958
  Node.alias newnode == name
959
    where _types = (node::Node.Node, name::String)
960
          newnode = Node.setAlias node name
961

    
962
prop_Node_setOffline node status =
963
  Node.offline newnode ==? status
964
    where newnode = Node.setOffline node status
965

    
966
prop_Node_setXmem node xm =
967
  Node.xMem newnode ==? xm
968
    where newnode = Node.setXmem node xm
969

    
970
prop_Node_setMcpu node mc =
971
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
972
    where newnode = Node.setMcpu node mc
973

    
974
-- | Check that an instance add with too high memory or disk will be
975
-- rejected.
976
prop_Node_addPriFM node inst =
977
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
978
  not (Instance.isOffline inst) ==>
979
  case Node.addPri node inst'' of
980
    Types.OpFail Types.FailMem -> True
981
    _ -> False
982
  where _types = (node::Node.Node, inst::Instance.Instance)
983
        inst' = setInstanceSmallerThanNode node inst
984
        inst'' = inst' { Instance.mem = Instance.mem inst }
985

    
986
prop_Node_addPriFD node inst =
987
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
988
    case Node.addPri node inst'' of
989
      Types.OpFail Types.FailDisk -> True
990
      _ -> False
991
    where _types = (node::Node.Node, inst::Instance.Instance)
992
          inst' = setInstanceSmallerThanNode node inst
993
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
994

    
995
prop_Node_addPriFC =
996
  forAll (choose (1, maxCpu)) $ \extra ->
997
  forAll genOnlineNode $ \node ->
998
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
999
  let inst' = setInstanceSmallerThanNode node inst
1000
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1001
  in case Node.addPri node inst'' of
1002
       Types.OpFail Types.FailCPU -> property True
1003
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1004

    
1005
-- | Check that an instance add with too high memory or disk will be
1006
-- rejected.
1007
prop_Node_addSec node inst pdx =
1008
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1009
    not (Instance.isOffline inst)) ||
1010
   Instance.dsk inst >= Node.fDsk node) &&
1011
  not (Node.failN1 node) ==>
1012
      isFailure (Node.addSec node inst pdx)
1013
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
1014

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

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

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

    
1073
-- | Check mdsk setting.
1074
prop_Node_setMdsk node mx =
1075
  Node.loDsk node' >= 0 &&
1076
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1077
  Node.availDisk node' >= 0 &&
1078
  Node.availDisk node' <= Node.fDsk node' &&
1079
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1080
  Node.mDsk node' == mx'
1081
    where _types = (node::Node.Node, mx::SmallRatio)
1082
          node' = Node.setMdsk node mx'
1083
          SmallRatio mx' = mx
1084

    
1085
-- Check tag maps
1086
prop_Node_tagMaps_idempotent =
1087
  forAll genTags $ \tags ->
1088
  Node.delTags (Node.addTags m tags) tags ==? m
1089
    where m = Data.Map.empty
1090

    
1091
prop_Node_tagMaps_reject =
1092
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1093
  let m = Node.addTags Data.Map.empty tags
1094
  in all (\t -> Node.rejectAddTags m [t]) tags
1095

    
1096
prop_Node_showField node =
1097
  forAll (elements Node.defaultFields) $ \ field ->
1098
  fst (Node.showHeader field) /= Types.unknownField &&
1099
  Node.showField node field /= Types.unknownField
1100

    
1101
prop_Node_computeGroups nodes =
1102
  let ng = Node.computeGroups nodes
1103
      onlyuuid = map fst ng
1104
  in length nodes == sum (map (length . snd) ng) &&
1105
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1106
     length (nub onlyuuid) == length onlyuuid &&
1107
     (null nodes || not (null ng))
1108

    
1109
-- Check idempotence of add/remove operations
1110
prop_Node_addPri_idempotent =
1111
  forAll genOnlineNode $ \node ->
1112
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1113
  case Node.addPri node inst of
1114
    Types.OpGood node' -> Node.removePri node' inst ==? node
1115
    _ -> failTest "Can't add instance"
1116

    
1117
prop_Node_addSec_idempotent =
1118
  forAll genOnlineNode $ \node ->
1119
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1120
  let pdx = Node.idx node + 1
1121
      inst' = Instance.setPri inst pdx
1122
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1123
  in case Node.addSec node inst'' pdx of
1124
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1125
       _ -> failTest "Can't add instance"
1126

    
1127
testSuite "Node"
1128
            [ 'prop_Node_setAlias
1129
            , 'prop_Node_setOffline
1130
            , 'prop_Node_setMcpu
1131
            , 'prop_Node_setXmem
1132
            , 'prop_Node_addPriFM
1133
            , 'prop_Node_addPriFD
1134
            , 'prop_Node_addPriFC
1135
            , 'prop_Node_addSec
1136
            , 'prop_Node_addOfflinePri
1137
            , 'prop_Node_addOfflineSec
1138
            , 'prop_Node_rMem
1139
            , 'prop_Node_setMdsk
1140
            , 'prop_Node_tagMaps_idempotent
1141
            , 'prop_Node_tagMaps_reject
1142
            , 'prop_Node_showField
1143
            , 'prop_Node_computeGroups
1144
            , 'prop_Node_addPri_idempotent
1145
            , 'prop_Node_addSec_idempotent
1146
            ]
1147

    
1148
-- ** Cluster tests
1149

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

    
1163
-- | Check that cluster stats are sane.
1164
prop_CStats_sane =
1165
  forAll (choose (1, 1024)) $ \count ->
1166
  forAll genOnlineNode $ \node ->
1167
  let fn = Node.buildPeers node Container.empty
1168
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1169
      nl = Container.fromList nlst
1170
      cstats = Cluster.totalResources nl
1171
  in Cluster.csAdsk cstats >= 0 &&
1172
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1173

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

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

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

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

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

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

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

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

    
1335
-- | Checks consistency.
1336
prop_ClusterCheckConsistency node inst =
1337
  let nl = makeSmallCluster node 3
1338
      [node1, node2, node3] = Container.elems nl
1339
      node3' = node3 { Node.group = 1 }
1340
      nl' = Container.add (Node.idx node3') node3' nl
1341
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1342
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1343
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1344
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1345
  in null (ccheck [(0, inst1)]) &&
1346
     null (ccheck [(0, inst2)]) &&
1347
     (not . null $ ccheck [(0, inst3)])
1348

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

    
1360
-- | Helper function to check if we can allocate an instance on a
1361
-- given node list.
1362
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1363
canAllocOn nl reqnodes inst =
1364
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1365
       Cluster.tryAlloc nl (Container.empty) inst of
1366
       Types.Bad _ -> False
1367
       Types.Ok as ->
1368
         case Cluster.asSolution as of
1369
           Nothing -> False
1370
           Just _ -> True
1371

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

    
1389
testSuite "Cluster"
1390
            [ 'prop_Score_Zero
1391
            , 'prop_CStats_sane
1392
            , 'prop_ClusterAlloc_sane
1393
            , 'prop_ClusterCanTieredAlloc
1394
            , 'prop_ClusterAllocRelocate
1395
            , 'prop_ClusterAllocEvacuate
1396
            , 'prop_ClusterAllocChangeGroup
1397
            , 'prop_ClusterAllocBalance
1398
            , 'prop_ClusterCheckConsistency
1399
            , 'prop_ClusterSplitCluster
1400
            , 'prop_ClusterAllocPolicy
1401
            ]
1402

    
1403
-- ** OpCodes tests
1404

    
1405
-- | Check that opcode serialization is idempotent.
1406
prop_OpCodes_serialization op =
1407
  case J.readJSON (J.showJSON op) of
1408
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1409
    J.Ok op' -> op ==? op'
1410
  where _types = op::OpCodes.OpCode
1411

    
1412
testSuite "OpCodes"
1413
            [ 'prop_OpCodes_serialization ]
1414

    
1415
-- ** Jobs tests
1416

    
1417
-- | Check that (queued) job\/opcode status serialization is idempotent.
1418
prop_OpStatus_serialization os =
1419
  case J.readJSON (J.showJSON os) of
1420
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1421
    J.Ok os' -> os ==? os'
1422
  where _types = os::Jobs.OpStatus
1423

    
1424
prop_JobStatus_serialization js =
1425
  case J.readJSON (J.showJSON js) of
1426
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1427
    J.Ok js' -> js ==? js'
1428
  where _types = js::Jobs.JobStatus
1429

    
1430
testSuite "Jobs"
1431
            [ 'prop_OpStatus_serialization
1432
            , 'prop_JobStatus_serialization
1433
            ]
1434

    
1435
-- ** Loader tests
1436

    
1437
prop_Loader_lookupNode ktn inst node =
1438
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1439
    where nl = Data.Map.fromList ktn
1440

    
1441
prop_Loader_lookupInstance kti inst =
1442
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1443
    where il = Data.Map.fromList kti
1444

    
1445
prop_Loader_assignIndices =
1446
  -- generate nodes with unique names
1447
  forAll (arbitrary `suchThat`
1448
          (\nodes ->
1449
             let names = map Node.name nodes
1450
             in length names == length (nub names))) $ \nodes ->
1451
  let (nassoc, kt) =
1452
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1453
  in Data.Map.size nassoc == length nodes &&
1454
     Container.size kt == length nodes &&
1455
     if not (null nodes)
1456
       then maximum (IntMap.keys kt) == length nodes - 1
1457
       else True
1458

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

    
1472
-- | Check that compareNameComponent on equal strings works.
1473
prop_Loader_compareNameComponent_equal :: String -> Bool
1474
prop_Loader_compareNameComponent_equal s =
1475
  Loader.compareNameComponent s s ==
1476
    Loader.LookupResult Loader.ExactMatch s
1477

    
1478
-- | Check that compareNameComponent on prefix strings works.
1479
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1480
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1481
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1482
    Loader.LookupResult Loader.PartialMatch s1
1483

    
1484
testSuite "Loader"
1485
            [ 'prop_Loader_lookupNode
1486
            , 'prop_Loader_lookupInstance
1487
            , 'prop_Loader_assignIndices
1488
            , 'prop_Loader_mergeData
1489
            , 'prop_Loader_compareNameComponent_equal
1490
            , 'prop_Loader_compareNameComponent_prefix
1491
            ]
1492

    
1493
-- ** Types tests
1494

    
1495
prop_Types_AllocPolicy_serialisation apol =
1496
  case J.readJSON (J.showJSON apol) of
1497
    J.Ok p -> p ==? apol
1498
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1499
      where _types = apol::Types.AllocPolicy
1500

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

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

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

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

    
1525
prop_Types_opToResult op =
1526
  case op of
1527
    Types.OpFail _ -> Types.isBad r
1528
    Types.OpGood v -> case r of
1529
                        Types.Bad _ -> False
1530
                        Types.Ok v' -> v == v'
1531
  where r = Types.opToResult op
1532
        _types = op::Types.OpResult Int
1533

    
1534
prop_Types_eitherToResult ei =
1535
  case ei of
1536
    Left _ -> Types.isBad r
1537
    Right v -> case r of
1538
                 Types.Bad _ -> False
1539
                 Types.Ok v' -> v == v'
1540
    where r = Types.eitherToResult ei
1541
          _types = ei::Either String Int
1542

    
1543
testSuite "Types"
1544
            [ 'prop_Types_AllocPolicy_serialisation
1545
            , 'prop_Types_DiskTemplate_serialisation
1546
            , 'prop_Types_ISpec_serialisation
1547
            , 'prop_Types_IPolicy_serialisation
1548
            , 'prop_Types_EvacMode_serialisation
1549
            , 'prop_Types_opToResult
1550
            , 'prop_Types_eitherToResult
1551
            ]
1552

    
1553
-- ** CLI tests
1554

    
1555
-- | Test correct parsing.
1556
prop_CLI_parseISpec descr dsk mem cpu =
1557
  let str = printf "%d,%d,%d" dsk mem cpu
1558
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1559

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

    
1569
-- | Test parseYesNo.
1570
prop_CLI_parseYesNo def testval val =
1571
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1572
  if testval
1573
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1574
    else let result = CLI.parseYesNo def (Just actual_val)
1575
         in if actual_val `elem` ["yes", "no"]
1576
              then result ==? Types.Ok (actual_val == "yes")
1577
              else property $ Types.isBad result
1578

    
1579
-- | Helper to check for correct parsing of string arg.
1580
checkStringArg val (opt, fn) =
1581
  let GetOpt.Option _ longs _ _ = opt
1582
  in case longs of
1583
       [] -> failTest "no long options?"
1584
       cmdarg:_ ->
1585
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1586
           Left e -> failTest $ "Failed to parse option: " ++ show e
1587
           Right (options, _) -> fn options ==? Just val
1588

    
1589
-- | Test a few string arguments.
1590
prop_CLI_StringArg argument =
1591
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1592
             , (CLI.oDynuFile,      CLI.optDynuFile)
1593
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1594
             , (CLI.oReplay,        CLI.optReplay)
1595
             , (CLI.oPrintCommands, CLI.optShowCmds)
1596
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1597
             ]
1598
  in conjoin $ map (checkStringArg argument) args
1599

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

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

    
1619
testSuite "CLI"
1620
          [ 'prop_CLI_parseISpec
1621
          , 'prop_CLI_parseISpecFail
1622
          , 'prop_CLI_parseYesNo
1623
          , 'prop_CLI_StringArg
1624
          , 'prop_CLI_stdopts
1625
          ]