Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (65.9 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittests for ganeti-htools.
4

    
5
-}
6

    
7
{-
8

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

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

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

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

    
26
-}
27

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

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

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

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

    
87
import Ganeti.HTools.QCHelper (testSuite)
88

    
89
-- * Constants
90

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

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

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

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

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

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

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

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

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

    
153

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

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

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

    
165
-- * Helper functions
166

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

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

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

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

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

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

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

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

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

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

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

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

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

    
260
-- * Arbitrary instances
261

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
508
-- * Actual tests
509

    
510
-- ** Utils tests
511

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

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

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

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

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

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

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

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

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

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

    
601
-- ** PeerMap tests
602

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

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

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

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

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

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

    
647
-- ** Container tests
648

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

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

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

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

    
691
-- ** Instance tests
692

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
783
-- ** Backends
784

    
785
-- *** Text backend tests
786

    
787
-- Instance text loader tests
788

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

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

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

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

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

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

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

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

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

    
937
-- *** Simu backend
938

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

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

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

    
988
-- ** Node tests
989

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1187
-- ** Cluster tests
1188

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1442
-- ** OpCodes tests
1443

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

    
1451
testSuite "OpCodes"
1452
            [ 'prop_OpCodes_serialization ]
1453

    
1454
-- ** Jobs tests
1455

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

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

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

    
1474
-- ** Loader tests
1475

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

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

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

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

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

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

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

    
1532
-- ** Types tests
1533

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

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

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

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

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

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

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

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

    
1592
-- ** CLI tests
1593

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

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

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

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

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

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

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

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

    
1666
-- * JSON tests
1667

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

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

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

    
1688
-- * Luxi tests
1689

    
1690
instance Arbitrary Luxi.LuxiReq where
1691
  arbitrary = elements [minBound..maxBound]
1692

    
1693
instance Arbitrary Luxi.QrViaLuxi where
1694
  arbitrary = elements [minBound..maxBound]
1695

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

    
1726
-- | Simple check that encoding/decoding of LuxiOp works.
1727
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1728
prop_Luxi_CallEncoding op =
1729
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1730

    
1731
testSuite "LUXI"
1732
          [ 'prop_Luxi_CallEncoding
1733
          ]