Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (70.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-}
3

    
4
-- FIXME: should remove the no-warn-unused-imports option, once we get
5
-- around to testing function from all modules; until then, we keep
6
-- the (unused) imports here to generate correct coverage (0 for
7
-- modules we don't use)
8

    
9
{-| Unittests for ganeti-htools.
10

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
16

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

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

    
34
module Ganeti.HTools.QC
35
  ( testUtils
36
  , testPeerMap
37
  , testContainer
38
  , testInstance
39
  , testNode
40
  , testText
41
  , testSimu
42
  , testOpCodes
43
  , testJobs
44
  , testCluster
45
  , testLoader
46
  , testTypes
47
  , testCLI
48
  , testJSON
49
  , testLUXI
50
  , testSsconf
51
  ) where
52

    
53
import Test.QuickCheck
54
import Text.Printf (printf)
55
import Data.List (intercalate, nub, isPrefixOf)
56
import Data.Maybe
57
import Control.Monad
58
import Control.Applicative
59
import qualified System.Console.GetOpt as GetOpt
60
import qualified Text.JSON as J
61
import qualified Data.Map
62
import qualified Data.IntMap as IntMap
63

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

    
88
import qualified Ganeti.HTools.Program as Program
89
import qualified Ganeti.HTools.Program.Hail
90
import qualified Ganeti.HTools.Program.Hbal
91
import qualified Ganeti.HTools.Program.Hscan
92
import qualified Ganeti.HTools.Program.Hspace
93

    
94
import Ganeti.HTools.QCHelper (testSuite)
95

    
96
-- * Constants
97

    
98
-- | Maximum memory (1TiB, somewhat random value).
99
maxMem :: Int
100
maxMem = 1024 * 1024
101

    
102
-- | Maximum disk (8TiB, somewhat random value).
103
maxDsk :: Int
104
maxDsk = 1024 * 1024 * 8
105

    
106
-- | Max CPUs (1024, somewhat random value).
107
maxCpu :: Int
108
maxCpu = 1024
109

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

    
114
-- | Max spindle ratio (random value).
115
maxSpindleRatio :: Double
116
maxSpindleRatio = 1024.0
117

    
118
-- | Max nodes, used just to limit arbitrary instances for smaller
119
-- opcode definitions (e.g. list of nodes in OpTestDelay).
120
maxNodes :: Int
121
maxNodes = 32
122

    
123
-- | Max opcodes or jobs in a submit job and submit many jobs.
124
maxOpCodes :: Int
125
maxOpCodes = 16
126

    
127
-- | All disk templates (used later)
128
allDiskTemplates :: [Types.DiskTemplate]
129
allDiskTemplates = [minBound..maxBound]
130

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

    
161

    
162
defGroup :: Group.Group
163
defGroup = flip Group.setIdx 0 $
164
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
165
                  nullIPolicy
166

    
167
defGroupList :: Group.List
168
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
169

    
170
defGroupAssoc :: Data.Map.Map String Types.Gdx
171
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
172

    
173
-- * Helper functions
174

    
175
-- | Simple checker for whether OpResult is fail or pass.
176
isFailure :: Types.OpResult a -> Bool
177
isFailure (Types.OpFail _) = True
178
isFailure _ = False
179

    
180
-- | Checks for equality with proper annotation.
181
(==?) :: (Show a, Eq a) => a -> a -> Property
182
(==?) x y = printTestCase
183
            ("Expected equality, but '" ++
184
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
185
infix 3 ==?
186

    
187
-- | Show a message and fail the test.
188
failTest :: String -> Property
189
failTest msg = printTestCase msg False
190

    
191
-- | Update an instance to be smaller than a node.
192
setInstanceSmallerThanNode :: Node.Node
193
                           -> Instance.Instance -> Instance.Instance
194
setInstanceSmallerThanNode node inst =
195
  inst { Instance.mem = Node.availMem node `div` 2
196
       , Instance.dsk = Node.availDisk node `div` 2
197
       , Instance.vcpus = Node.availCpu node `div` 2
198
       }
199

    
200
-- | Create an instance given its spec.
201
createInstance :: Int -> Int -> Int -> Instance.Instance
202
createInstance mem dsk vcpus =
203
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
204
    Types.DTDrbd8 1
205

    
206
-- | Create a small cluster by repeating a node spec.
207
makeSmallCluster :: Node.Node -> Int -> Node.List
208
makeSmallCluster node count =
209
  let origname = Node.name node
210
      origalias = Node.alias node
211
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
212
                                , Node.alias = origalias ++ "-" ++ show idx })
213
              [1..count]
214
      fn = flip Node.buildPeers Container.empty
215
      namelst = map (\n -> (Node.name n, fn n)) nodes
216
      (_, nlst) = Loader.assignIndices namelst
217
  in nlst
218

    
219
-- | Make a small cluster, both nodes and instances.
220
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
221
                      -> (Node.List, Instance.List, Instance.Instance)
222
makeSmallEmptyCluster node count inst =
223
  (makeSmallCluster node count, Container.empty,
224
   setInstanceSmallerThanNode node inst)
225

    
226
-- | Checks if a node is "big" enough.
227
isNodeBig :: Int -> Node.Node -> Bool
228
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
229
                      && Node.availMem node > size * Types.unitMem
230
                      && Node.availCpu node > size * Types.unitCpu
231

    
232
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
233
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
234

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

    
254
-- | Generates a list of a given size with non-duplicate elements.
255
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
256
genUniquesList cnt =
257
  foldM (\lst _ -> do
258
           newelem <- arbitrary `suchThat` (`notElem` lst)
259
           return (newelem:lst)) [] [1..cnt]
260

    
261
-- | Checks if an instance is mirrored.
262
isMirrored :: Instance.Instance -> Bool
263
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
264

    
265
-- | Returns the possible change node types for a disk template.
266
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
267
evacModeOptions Types.MirrorNone     = []
268
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
269
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
270

    
271
-- * Arbitrary instances
272

    
273
-- | Defines a DNS name.
274
newtype DNSChar = DNSChar { dnsGetChar::Char }
275

    
276
instance Arbitrary DNSChar where
277
  arbitrary = do
278
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
279
    return (DNSChar x)
280

    
281
-- | Generates a single name component.
282
getName :: Gen String
283
getName = do
284
  n <- choose (1, 64)
285
  dn <- vector n
286
  return (map dnsGetChar dn)
287

    
288
-- | Generates an entire FQDN.
289
getFQDN :: Gen String
290
getFQDN = do
291
  ncomps <- choose (1, 4)
292
  names <- vectorOf ncomps getName
293
  return $ intercalate "." names
294

    
295
-- | Combinator that generates a 'Maybe' using a sub-combinator.
296
getMaybe :: Gen a -> Gen (Maybe a)
297
getMaybe subgen = do
298
  bool <- arbitrary
299
  if bool
300
    then Just <$> subgen
301
    else return Nothing
302

    
303
-- | Generates a fields list. This uses the same character set as a
304
-- DNS name (just for simplicity).
305
getFields :: Gen [String]
306
getFields = do
307
  n <- choose (1, 32)
308
  vectorOf n getName
309

    
310
-- | Defines a tag type.
311
newtype TagChar = TagChar { tagGetChar :: Char }
312

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

    
318
instance Arbitrary TagChar where
319
  arbitrary = do
320
    c <- elements tagChar
321
    return (TagChar c)
322

    
323
-- | Generates a tag
324
genTag :: Gen [TagChar]
325
genTag = do
326
  -- the correct value would be C.maxTagLen, but that's way too
327
  -- verbose in unittests, and at the moment I don't see any possible
328
  -- bugs with longer tags and the way we use tags in htools
329
  n <- choose (1, 10)
330
  vector n
331

    
332
-- | Generates a list of tags (correctly upper bounded).
333
genTags :: Gen [String]
334
genTags = do
335
  -- the correct value would be C.maxTagsPerObj, but per the comment
336
  -- in genTag, we don't use tags enough in htools to warrant testing
337
  -- such big values
338
  n <- choose (0, 10::Int)
339
  tags <- mapM (const genTag) [1..n]
340
  return $ map (map tagGetChar) tags
341

    
342
instance Arbitrary Types.InstanceStatus where
343
    arbitrary = elements [minBound..maxBound]
344

    
345
-- | Generates a random instance with maximum disk/mem/cpu values.
346
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
347
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
348
  name <- getFQDN
349
  mem <- choose (0, lim_mem)
350
  dsk <- choose (0, lim_dsk)
351
  run_st <- arbitrary
352
  pn <- arbitrary
353
  sn <- arbitrary
354
  vcpus <- choose (0, lim_cpu)
355
  dt <- arbitrary
356
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
357

    
358
-- | Generates an instance smaller than a node.
359
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
360
genInstanceSmallerThanNode node =
361
  genInstanceSmallerThan (Node.availMem node `div` 2)
362
                         (Node.availDisk node `div` 2)
363
                         (Node.availCpu node `div` 2)
364

    
365
-- let's generate a random instance
366
instance Arbitrary Instance.Instance where
367
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
368

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

    
400
-- | Helper function to generate a sane node.
401
genOnlineNode :: Gen Node.Node
402
genOnlineNode = do
403
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
404
                              not (Node.failN1 n) &&
405
                              Node.availDisk n > 0 &&
406
                              Node.availMem n > 0 &&
407
                              Node.availCpu n > 0)
408

    
409
-- and a random node
410
instance Arbitrary Node.Node where
411
  arbitrary = genNode Nothing Nothing
412

    
413
-- replace disks
414
instance Arbitrary OpCodes.ReplaceDisksMode where
415
  arbitrary = elements [minBound..maxBound]
416

    
417
instance Arbitrary OpCodes.OpCode where
418
  arbitrary = do
419
    op_id <- elements [ "OP_TEST_DELAY"
420
                      , "OP_INSTANCE_REPLACE_DISKS"
421
                      , "OP_INSTANCE_FAILOVER"
422
                      , "OP_INSTANCE_MIGRATE"
423
                      ]
424
    case op_id of
425
      "OP_TEST_DELAY" ->
426
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
427
                 <*> resize maxNodes (listOf getFQDN)
428
      "OP_INSTANCE_REPLACE_DISKS" ->
429
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
430
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
431
      "OP_INSTANCE_FAILOVER" ->
432
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
433
          getMaybe getFQDN
434
      "OP_INSTANCE_MIGRATE" ->
435
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
436
          arbitrary <*> arbitrary <*> getMaybe getFQDN
437
      _ -> fail "Wrong opcode"
438

    
439
instance Arbitrary Jobs.OpStatus where
440
  arbitrary = elements [minBound..maxBound]
441

    
442
instance Arbitrary Jobs.JobStatus where
443
  arbitrary = elements [minBound..maxBound]
444

    
445
newtype SmallRatio = SmallRatio Double deriving Show
446
instance Arbitrary SmallRatio where
447
  arbitrary = do
448
    v <- choose (0, 1)
449
    return $ SmallRatio v
450

    
451
instance Arbitrary Types.AllocPolicy where
452
  arbitrary = elements [minBound..maxBound]
453

    
454
instance Arbitrary Types.DiskTemplate where
455
  arbitrary = elements [minBound..maxBound]
456

    
457
instance Arbitrary Types.FailMode where
458
  arbitrary = elements [minBound..maxBound]
459

    
460
instance Arbitrary Types.EvacMode where
461
  arbitrary = elements [minBound..maxBound]
462

    
463
instance Arbitrary a => Arbitrary (Types.OpResult a) where
464
  arbitrary = arbitrary >>= \c ->
465
              if c
466
                then Types.OpGood <$> arbitrary
467
                else Types.OpFail <$> arbitrary
468

    
469
instance Arbitrary Types.ISpec where
470
  arbitrary = do
471
    mem_s <- arbitrary::Gen (NonNegative Int)
472
    dsk_c <- arbitrary::Gen (NonNegative Int)
473
    dsk_s <- arbitrary::Gen (NonNegative Int)
474
    cpu_c <- arbitrary::Gen (NonNegative Int)
475
    nic_c <- arbitrary::Gen (NonNegative Int)
476
    su    <- arbitrary::Gen (NonNegative Int)
477
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
478
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
479
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
480
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
481
                       , Types.iSpecNicCount   = fromIntegral nic_c
482
                       , Types.iSpecSpindleUse = fromIntegral su
483
                       }
484

    
485
-- | Generates an ispec bigger than the given one.
486
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
487
genBiggerISpec imin = do
488
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
489
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
490
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
491
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
492
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
493
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
494
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
495
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
496
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
497
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
498
                     , Types.iSpecNicCount   = fromIntegral nic_c
499
                     , Types.iSpecSpindleUse = fromIntegral su
500
                     }
501

    
502
instance Arbitrary Types.IPolicy where
503
  arbitrary = do
504
    imin <- arbitrary
505
    istd <- genBiggerISpec imin
506
    imax <- genBiggerISpec istd
507
    num_tmpl <- choose (0, length allDiskTemplates)
508
    dts  <- genUniquesList num_tmpl
509
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
510
    spindle_ratio <- choose (1.0, maxSpindleRatio)
511
    return Types.IPolicy { Types.iPolicyMinSpec = imin
512
                         , Types.iPolicyStdSpec = istd
513
                         , Types.iPolicyMaxSpec = imax
514
                         , Types.iPolicyDiskTemplates = dts
515
                         , Types.iPolicyVcpuRatio = vcpu_ratio
516
                         , Types.iPolicySpindleRatio = spindle_ratio
517
                         }
518

    
519
-- * Actual tests
520

    
521
-- ** Utils tests
522

    
523
-- | Helper to generate a small string that doesn't contain commas.
524
genNonCommaString :: Gen [Char]
525
genNonCommaString = do
526
  size <- choose (0, 20) -- arbitrary max size
527
  vectorOf size (arbitrary `suchThat` ((/=) ','))
528

    
529
-- | If the list is not just an empty element, and if the elements do
530
-- not contain commas, then join+split should be idempotent.
531
prop_Utils_commaJoinSplit :: Property
532
prop_Utils_commaJoinSplit =
533
  forAll (choose (0, 20)) $ \llen ->
534
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
535
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
536

    
537
-- | Split and join should always be idempotent.
538
prop_Utils_commaSplitJoin :: [Char] -> Property
539
prop_Utils_commaSplitJoin s =
540
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
541

    
542
-- | fromObjWithDefault, we test using the Maybe monad and an integer
543
-- value.
544
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
545
prop_Utils_fromObjWithDefault def_value random_key =
546
  -- a missing key will be returned with the default
547
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
548
  -- a found key will be returned as is, not with default
549
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
550
       random_key (def_value+1) == Just def_value
551

    
552
-- | Test that functional if' behaves like the syntactic sugar if.
553
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
554
prop_Utils_if'if cnd a b =
555
  Utils.if' cnd a b ==? if cnd then a else b
556

    
557
-- | Test basic select functionality
558
prop_Utils_select :: Int      -- ^ Default result
559
                  -> [Int]    -- ^ List of False values
560
                  -> [Int]    -- ^ List of True values
561
                  -> Gen Prop -- ^ Test result
562
prop_Utils_select def lst1 lst2 =
563
  Utils.select def (flist ++ tlist) ==? expectedresult
564
    where expectedresult = Utils.if' (null lst2) def (head lst2)
565
          flist = zip (repeat False) lst1
566
          tlist = zip (repeat True)  lst2
567

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

    
577
-- | Test basic select functionality with undefined list values
578
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
579
                         -> NonEmptyList Int -- ^ List of True values
580
                         -> Gen Prop         -- ^ Test result
581
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
582
  Utils.select undefined cndlist ==? head lst2
583
    where flist = zip (repeat False) lst1
584
          tlist = zip (repeat True)  lst2
585
          cndlist = flist ++ tlist ++ [undefined]
586

    
587
prop_Utils_parseUnit :: NonNegative Int -> Property
588
prop_Utils_parseUnit (NonNegative n) =
589
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
590
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
591
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
592
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
593
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
594
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
595
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
596
  printTestCase "Internal error/overflow?"
597
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
598
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
599
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
600
        n_gb = n_mb * 1000
601
        n_tb = n_gb * 1000
602

    
603
-- | Test list for the Utils module.
604
testSuite "Utils"
605
            [ 'prop_Utils_commaJoinSplit
606
            , 'prop_Utils_commaSplitJoin
607
            , 'prop_Utils_fromObjWithDefault
608
            , 'prop_Utils_if'if
609
            , 'prop_Utils_select
610
            , 'prop_Utils_select_undefd
611
            , 'prop_Utils_select_undefv
612
            , 'prop_Utils_parseUnit
613
            ]
614

    
615
-- ** PeerMap tests
616

    
617
-- | Make sure add is idempotent.
618
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
619
                           -> PeerMap.Key -> PeerMap.Elem -> Property
620
prop_PeerMap_addIdempotent pmap key em =
621
  fn puniq ==? fn (fn puniq)
622
    where fn = PeerMap.add key em
623
          puniq = PeerMap.accumArray const pmap
624

    
625
-- | Make sure remove is idempotent.
626
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
627
prop_PeerMap_removeIdempotent pmap key =
628
  fn puniq ==? fn (fn puniq)
629
    where fn = PeerMap.remove key
630
          puniq = PeerMap.accumArray const pmap
631

    
632
-- | Make sure a missing item returns 0.
633
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
634
prop_PeerMap_findMissing pmap key =
635
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
636
    where puniq = PeerMap.accumArray const pmap
637

    
638
-- | Make sure an added item is found.
639
prop_PeerMap_addFind :: PeerMap.PeerMap
640
                     -> PeerMap.Key -> PeerMap.Elem -> Property
641
prop_PeerMap_addFind pmap key em =
642
  PeerMap.find key (PeerMap.add key em puniq) ==? em
643
    where puniq = PeerMap.accumArray const pmap
644

    
645
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
646
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
647
prop_PeerMap_maxElem pmap =
648
  PeerMap.maxElem puniq ==? if null puniq then 0
649
                              else (maximum . snd . unzip) puniq
650
    where puniq = PeerMap.accumArray const pmap
651

    
652
-- | List of tests for the PeerMap module.
653
testSuite "PeerMap"
654
            [ 'prop_PeerMap_addIdempotent
655
            , 'prop_PeerMap_removeIdempotent
656
            , 'prop_PeerMap_maxElem
657
            , 'prop_PeerMap_addFind
658
            , 'prop_PeerMap_findMissing
659
            ]
660

    
661
-- ** Container tests
662

    
663
-- we silence the following due to hlint bug fixed in later versions
664
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
665
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
666
prop_Container_addTwo cdata i1 i2 =
667
  fn i1 i2 cont == fn i2 i1 cont &&
668
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
669
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
670
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
671

    
672
prop_Container_nameOf :: Node.Node -> Property
673
prop_Container_nameOf node =
674
  let nl = makeSmallCluster node 1
675
      fnode = head (Container.elems nl)
676
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
677

    
678
-- | We test that in a cluster, given a random node, we can find it by
679
-- its name and alias, as long as all names and aliases are unique,
680
-- and that we fail to find a non-existing name.
681
prop_Container_findByName :: Node.Node -> Property
682
prop_Container_findByName node =
683
  forAll (choose (1, 20)) $ \ cnt ->
684
  forAll (choose (0, cnt - 1)) $ \ fidx ->
685
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
686
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
687
  let names = zip (take cnt allnames) (drop cnt allnames)
688
      nl = makeSmallCluster node cnt
689
      nodes = Container.elems nl
690
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
691
                                             nn { Node.name = name,
692
                                                  Node.alias = alias }))
693
               $ zip names nodes
694
      nl' = Container.fromList nodes'
695
      target = snd (nodes' !! fidx)
696
  in Container.findByName nl' (Node.name target) == Just target &&
697
     Container.findByName nl' (Node.alias target) == Just target &&
698
     isNothing (Container.findByName nl' othername)
699

    
700
testSuite "Container"
701
            [ 'prop_Container_addTwo
702
            , 'prop_Container_nameOf
703
            , 'prop_Container_findByName
704
            ]
705

    
706
-- ** Instance tests
707

    
708
-- Simple instance tests, we only have setter/getters
709

    
710
prop_Instance_creat :: Instance.Instance -> Property
711
prop_Instance_creat inst =
712
  Instance.name inst ==? Instance.alias inst
713

    
714
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
715
prop_Instance_setIdx inst idx =
716
  Instance.idx (Instance.setIdx inst idx) ==? idx
717

    
718
prop_Instance_setName :: Instance.Instance -> String -> Bool
719
prop_Instance_setName inst name =
720
  Instance.name newinst == name &&
721
  Instance.alias newinst == name
722
    where newinst = Instance.setName inst name
723

    
724
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
725
prop_Instance_setAlias inst name =
726
  Instance.name newinst == Instance.name inst &&
727
  Instance.alias newinst == name
728
    where newinst = Instance.setAlias inst name
729

    
730
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
731
prop_Instance_setPri inst pdx =
732
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
733

    
734
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
735
prop_Instance_setSec inst sdx =
736
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
737

    
738
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
739
prop_Instance_setBoth inst pdx sdx =
740
  Instance.pNode si == pdx && Instance.sNode si == sdx
741
    where si = Instance.setBoth inst pdx sdx
742

    
743
prop_Instance_shrinkMG :: Instance.Instance -> Property
744
prop_Instance_shrinkMG inst =
745
  Instance.mem inst >= 2 * Types.unitMem ==>
746
    case Instance.shrinkByType inst Types.FailMem of
747
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
748
      _ -> False
749

    
750
prop_Instance_shrinkMF :: Instance.Instance -> Property
751
prop_Instance_shrinkMF inst =
752
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
753
    let inst' = inst { Instance.mem = mem}
754
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
755

    
756
prop_Instance_shrinkCG :: Instance.Instance -> Property
757
prop_Instance_shrinkCG inst =
758
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
759
    case Instance.shrinkByType inst Types.FailCPU of
760
      Types.Ok inst' ->
761
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
762
      _ -> False
763

    
764
prop_Instance_shrinkCF :: Instance.Instance -> Property
765
prop_Instance_shrinkCF inst =
766
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
767
    let inst' = inst { Instance.vcpus = vcpus }
768
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
769

    
770
prop_Instance_shrinkDG :: Instance.Instance -> Property
771
prop_Instance_shrinkDG inst =
772
  Instance.dsk inst >= 2 * Types.unitDsk ==>
773
    case Instance.shrinkByType inst Types.FailDisk of
774
      Types.Ok inst' ->
775
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
776
      _ -> False
777

    
778
prop_Instance_shrinkDF :: Instance.Instance -> Property
779
prop_Instance_shrinkDF inst =
780
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
781
    let inst' = inst { Instance.dsk = dsk }
782
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
783

    
784
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
785
prop_Instance_setMovable inst m =
786
  Instance.movable inst' ==? m
787
    where inst' = Instance.setMovable inst m
788

    
789
testSuite "Instance"
790
            [ 'prop_Instance_creat
791
            , 'prop_Instance_setIdx
792
            , 'prop_Instance_setName
793
            , 'prop_Instance_setAlias
794
            , 'prop_Instance_setPri
795
            , 'prop_Instance_setSec
796
            , 'prop_Instance_setBoth
797
            , 'prop_Instance_shrinkMG
798
            , 'prop_Instance_shrinkMF
799
            , 'prop_Instance_shrinkCG
800
            , 'prop_Instance_shrinkCF
801
            , 'prop_Instance_shrinkDG
802
            , 'prop_Instance_shrinkDF
803
            , 'prop_Instance_setMovable
804
            ]
805

    
806
-- ** Backends
807

    
808
-- *** Text backend tests
809

    
810
-- Instance text loader tests
811

    
812
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
813
                        -> NonEmptyList Char -> [Char]
814
                        -> NonNegative Int -> NonNegative Int -> Bool
815
                        -> Types.DiskTemplate -> Int -> Property
816
prop_Text_Load_Instance name mem dsk vcpus status
817
                        (NonEmpty pnode) snode
818
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
819
  pnode /= snode && pdx /= sdx ==>
820
  let vcpus_s = show vcpus
821
      dsk_s = show dsk
822
      mem_s = show mem
823
      su_s = show su
824
      status_s = Types.instanceStatusToRaw status
825
      ndx = if null snode
826
              then [(pnode, pdx)]
827
              else [(pnode, pdx), (snode, sdx)]
828
      nl = Data.Map.fromList ndx
829
      tags = ""
830
      sbal = if autobal then "Y" else "N"
831
      sdt = Types.diskTemplateToRaw dt
832
      inst = Text.loadInst nl
833
             [name, mem_s, dsk_s, vcpus_s, status_s,
834
              sbal, pnode, snode, sdt, tags, su_s]
835
      fail1 = Text.loadInst nl
836
              [name, mem_s, dsk_s, vcpus_s, status_s,
837
               sbal, pnode, pnode, tags]
838
  in case inst of
839
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
840
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
841
                                        \ loading the instance" $
842
               Instance.name i == name &&
843
               Instance.vcpus i == vcpus &&
844
               Instance.mem i == mem &&
845
               Instance.pNode i == pdx &&
846
               Instance.sNode i == (if null snode
847
                                      then Node.noSecondary
848
                                      else sdx) &&
849
               Instance.autoBalance i == autobal &&
850
               Instance.spindleUse i == su &&
851
               Types.isBad fail1
852

    
853
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
854
prop_Text_Load_InstanceFail ktn fields =
855
  length fields /= 10 && length fields /= 11 ==>
856
    case Text.loadInst nl fields of
857
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
858
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
859
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
860
    where nl = Data.Map.fromList ktn
861

    
862
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
863
                    -> Int -> Bool -> Bool
864
prop_Text_Load_Node name tm nm fm td fd tc fo =
865
  let conv v = if v < 0
866
                 then "?"
867
                 else show v
868
      tm_s = conv tm
869
      nm_s = conv nm
870
      fm_s = conv fm
871
      td_s = conv td
872
      fd_s = conv fd
873
      tc_s = conv tc
874
      fo_s = if fo
875
               then "Y"
876
               else "N"
877
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
878
      gid = Group.uuid defGroup
879
  in case Text.loadNode defGroupAssoc
880
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
881
       Nothing -> False
882
       Just (name', node) ->
883
         if fo || any_broken
884
           then Node.offline node
885
           else Node.name node == name' && name' == name &&
886
                Node.alias node == name &&
887
                Node.tMem node == fromIntegral tm &&
888
                Node.nMem node == nm &&
889
                Node.fMem node == fm &&
890
                Node.tDsk node == fromIntegral td &&
891
                Node.fDsk node == fd &&
892
                Node.tCpu node == fromIntegral tc
893

    
894
prop_Text_Load_NodeFail :: [String] -> Property
895
prop_Text_Load_NodeFail fields =
896
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
897

    
898
prop_Text_NodeLSIdempotent :: Node.Node -> Property
899
prop_Text_NodeLSIdempotent node =
900
  (Text.loadNode defGroupAssoc.
901
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
902
  Just (Node.name n, n)
903
    -- override failN1 to what loadNode returns by default
904
    where n = Node.setPolicy Types.defIPolicy $
905
              node { Node.failN1 = True, Node.offline = False }
906

    
907
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
908
prop_Text_ISpecIdempotent ispec =
909
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
910
       Text.serializeISpec $ ispec of
911
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
912
    Types.Ok ispec' -> ispec ==? ispec'
913

    
914
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
915
prop_Text_IPolicyIdempotent ipol =
916
  case Text.loadIPolicy . Utils.sepSplit '|' $
917
       Text.serializeIPolicy owner ipol of
918
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
919
    Types.Ok res -> (owner, ipol) ==? res
920
  where owner = "dummy"
921

    
922
-- | This property, while being in the text tests, does more than just
923
-- test end-to-end the serialisation and loading back workflow; it
924
-- also tests the Loader.mergeData and the actuall
925
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
926
-- allocations, not for the business logic). As such, it's a quite
927
-- complex and slow test, and that's the reason we restrict it to
928
-- small cluster sizes.
929
prop_Text_CreateSerialise :: Property
930
prop_Text_CreateSerialise =
931
  forAll genTags $ \ctags ->
932
  forAll (choose (1, 20)) $ \maxiter ->
933
  forAll (choose (2, 10)) $ \count ->
934
  forAll genOnlineNode $ \node ->
935
  forAll (genInstanceSmallerThanNode node) $ \inst ->
936
  let nl = makeSmallCluster node count
937
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
938
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
939
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
940
     of
941
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
942
       Types.Ok (_, _, _, [], _) -> printTestCase
943
                                    "Failed to allocate: no allocations" False
944
       Types.Ok (_, nl', il', _, _) ->
945
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
946
                     Types.defIPolicy
947
             saved = Text.serializeCluster cdata
948
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
949
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
950
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
951
                ctags ==? ctags2 .&&.
952
                Types.defIPolicy ==? cpol2 .&&.
953
                il' ==? il2 .&&.
954
                defGroupList ==? gl2 .&&.
955
                nl' ==? nl2
956

    
957
testSuite "Text"
958
            [ 'prop_Text_Load_Instance
959
            , 'prop_Text_Load_InstanceFail
960
            , 'prop_Text_Load_Node
961
            , 'prop_Text_Load_NodeFail
962
            , 'prop_Text_NodeLSIdempotent
963
            , 'prop_Text_ISpecIdempotent
964
            , 'prop_Text_IPolicyIdempotent
965
            , 'prop_Text_CreateSerialise
966
            ]
967

    
968
-- *** Simu backend
969

    
970
-- | Generates a tuple of specs for simulation.
971
genSimuSpec :: Gen (String, Int, Int, Int, Int)
972
genSimuSpec = do
973
  pol <- elements [C.allocPolicyPreferred,
974
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
975
                  "p", "a", "u"]
976
 -- should be reasonable (nodes/group), bigger values only complicate
977
 -- the display of failed tests, and we don't care (in this particular
978
 -- test) about big node groups
979
  nodes <- choose (0, 20)
980
  dsk <- choose (0, maxDsk)
981
  mem <- choose (0, maxMem)
982
  cpu <- choose (0, maxCpu)
983
  return (pol, nodes, dsk, mem, cpu)
984

    
985
-- | Checks that given a set of corrects specs, we can load them
986
-- successfully, and that at high-level the values look right.
987
prop_SimuLoad :: Property
988
prop_SimuLoad =
989
  forAll (choose (0, 10)) $ \ngroups ->
990
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
991
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
992
                                          p n d m c::String) specs
993
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
994
      mdc_in = concatMap (\(_, n, d, m, c) ->
995
                            replicate n (fromIntegral m, fromIntegral d,
996
                                         fromIntegral c,
997
                                         fromIntegral m, fromIntegral d))
998
               specs :: [(Double, Double, Double, Int, Int)]
999
  in case Simu.parseData strspecs of
1000
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1001
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1002
         let nodes = map snd $ IntMap.toAscList nl
1003
             nidx = map Node.idx nodes
1004
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1005
                                   Node.fMem n, Node.fDsk n)) nodes
1006
         in
1007
         Container.size gl ==? ngroups .&&.
1008
         Container.size nl ==? totnodes .&&.
1009
         Container.size il ==? 0 .&&.
1010
         length tags ==? 0 .&&.
1011
         ipol ==? Types.defIPolicy .&&.
1012
         nidx ==? [1..totnodes] .&&.
1013
         mdc_in ==? mdc_out .&&.
1014
         map Group.iPolicy (Container.elems gl) ==?
1015
             replicate ngroups Types.defIPolicy
1016

    
1017
testSuite "Simu"
1018
            [ 'prop_SimuLoad
1019
            ]
1020

    
1021
-- ** Node tests
1022

    
1023
prop_Node_setAlias :: Node.Node -> String -> Bool
1024
prop_Node_setAlias node name =
1025
  Node.name newnode == Node.name node &&
1026
  Node.alias newnode == name
1027
    where newnode = Node.setAlias node name
1028

    
1029
prop_Node_setOffline :: Node.Node -> Bool -> Property
1030
prop_Node_setOffline node status =
1031
  Node.offline newnode ==? status
1032
    where newnode = Node.setOffline node status
1033

    
1034
prop_Node_setXmem :: Node.Node -> Int -> Property
1035
prop_Node_setXmem node xm =
1036
  Node.xMem newnode ==? xm
1037
    where newnode = Node.setXmem node xm
1038

    
1039
prop_Node_setMcpu :: Node.Node -> Double -> Property
1040
prop_Node_setMcpu node mc =
1041
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1042
    where newnode = Node.setMcpu node mc
1043

    
1044
-- | Check that an instance add with too high memory or disk will be
1045
-- rejected.
1046
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1047
prop_Node_addPriFM node inst =
1048
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1049
  not (Instance.isOffline inst) ==>
1050
  case Node.addPri node inst'' of
1051
    Types.OpFail Types.FailMem -> True
1052
    _ -> False
1053
  where inst' = setInstanceSmallerThanNode node inst
1054
        inst'' = inst' { Instance.mem = Instance.mem inst }
1055

    
1056
-- | Check that adding a primary instance with too much disk fails
1057
-- with type FailDisk.
1058
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1059
prop_Node_addPriFD node inst =
1060
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1061
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1062
  let inst' = setInstanceSmallerThanNode node inst
1063
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1064
                     , Instance.diskTemplate = dt }
1065
  in case Node.addPri node inst'' of
1066
       Types.OpFail Types.FailDisk -> True
1067
       _ -> False
1068

    
1069
-- | Check that adding a primary instance with too many VCPUs fails
1070
-- with type FailCPU.
1071
prop_Node_addPriFC :: Property
1072
prop_Node_addPriFC =
1073
  forAll (choose (1, maxCpu)) $ \extra ->
1074
  forAll genOnlineNode $ \node ->
1075
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1076
  let inst' = setInstanceSmallerThanNode node inst
1077
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1078
  in case Node.addPri node inst'' of
1079
       Types.OpFail Types.FailCPU -> property True
1080
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1081

    
1082
-- | Check that an instance add with too high memory or disk will be
1083
-- rejected.
1084
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1085
prop_Node_addSec node inst pdx =
1086
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1087
    not (Instance.isOffline inst)) ||
1088
   Instance.dsk inst >= Node.fDsk node) &&
1089
  not (Node.failN1 node) ==>
1090
      isFailure (Node.addSec node inst pdx)
1091

    
1092
-- | Check that an offline instance with reasonable disk size but
1093
-- extra mem/cpu can always be added.
1094
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1095
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1096
  forAll genOnlineNode $ \node ->
1097
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1098
  let inst' = inst { Instance.runSt = Types.AdminOffline
1099
                   , Instance.mem = Node.availMem node + extra_mem
1100
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1101
  in case Node.addPri node inst' of
1102
       Types.OpGood _ -> property True
1103
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1104

    
1105
-- | Check that an offline instance with reasonable disk size but
1106
-- extra mem/cpu can always be added.
1107
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1108
                        -> Types.Ndx -> Property
1109
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1110
  forAll genOnlineNode $ \node ->
1111
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1112
  let inst' = inst { Instance.runSt = Types.AdminOffline
1113
                   , Instance.mem = Node.availMem node + extra_mem
1114
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1115
                   , Instance.diskTemplate = Types.DTDrbd8 }
1116
  in case Node.addSec node inst' pdx of
1117
       Types.OpGood _ -> property True
1118
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1119

    
1120
-- | Checks for memory reservation changes.
1121
prop_Node_rMem :: Instance.Instance -> Property
1122
prop_Node_rMem inst =
1123
  not (Instance.isOffline inst) ==>
1124
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1125
  -- ab = auto_balance, nb = non-auto_balance
1126
  -- we use -1 as the primary node of the instance
1127
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1128
                   , Instance.diskTemplate = Types.DTDrbd8 }
1129
      inst_ab = setInstanceSmallerThanNode node inst'
1130
      inst_nb = inst_ab { Instance.autoBalance = False }
1131
      -- now we have the two instances, identical except the
1132
      -- autoBalance attribute
1133
      orig_rmem = Node.rMem node
1134
      inst_idx = Instance.idx inst_ab
1135
      node_add_ab = Node.addSec node inst_ab (-1)
1136
      node_add_nb = Node.addSec node inst_nb (-1)
1137
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1138
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1139
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1140
       (Types.OpGood a_ab, Types.OpGood a_nb,
1141
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1142
         printTestCase "Consistency checks failed" $
1143
           Node.rMem a_ab >  orig_rmem &&
1144
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1145
           Node.rMem a_nb == orig_rmem &&
1146
           Node.rMem d_ab == orig_rmem &&
1147
           Node.rMem d_nb == orig_rmem &&
1148
           -- this is not related to rMem, but as good a place to
1149
           -- test as any
1150
           inst_idx `elem` Node.sList a_ab &&
1151
           inst_idx `notElem` Node.sList d_ab
1152
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1153

    
1154
-- | Check mdsk setting.
1155
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1156
prop_Node_setMdsk node mx =
1157
  Node.loDsk node' >= 0 &&
1158
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1159
  Node.availDisk node' >= 0 &&
1160
  Node.availDisk node' <= Node.fDsk node' &&
1161
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1162
  Node.mDsk node' == mx'
1163
    where node' = Node.setMdsk node mx'
1164
          SmallRatio mx' = mx
1165

    
1166
-- Check tag maps
1167
prop_Node_tagMaps_idempotent :: Property
1168
prop_Node_tagMaps_idempotent =
1169
  forAll genTags $ \tags ->
1170
  Node.delTags (Node.addTags m tags) tags ==? m
1171
    where m = Data.Map.empty
1172

    
1173
prop_Node_tagMaps_reject :: Property
1174
prop_Node_tagMaps_reject =
1175
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1176
  let m = Node.addTags Data.Map.empty tags
1177
  in all (\t -> Node.rejectAddTags m [t]) tags
1178

    
1179
prop_Node_showField :: Node.Node -> Property
1180
prop_Node_showField node =
1181
  forAll (elements Node.defaultFields) $ \ field ->
1182
  fst (Node.showHeader field) /= Types.unknownField &&
1183
  Node.showField node field /= Types.unknownField
1184

    
1185
prop_Node_computeGroups :: [Node.Node] -> Bool
1186
prop_Node_computeGroups nodes =
1187
  let ng = Node.computeGroups nodes
1188
      onlyuuid = map fst ng
1189
  in length nodes == sum (map (length . snd) ng) &&
1190
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1191
     length (nub onlyuuid) == length onlyuuid &&
1192
     (null nodes || not (null ng))
1193

    
1194
-- Check idempotence of add/remove operations
1195
prop_Node_addPri_idempotent :: Property
1196
prop_Node_addPri_idempotent =
1197
  forAll genOnlineNode $ \node ->
1198
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1199
  case Node.addPri node inst of
1200
    Types.OpGood node' -> Node.removePri node' inst ==? node
1201
    _ -> failTest "Can't add instance"
1202

    
1203
prop_Node_addSec_idempotent :: Property
1204
prop_Node_addSec_idempotent =
1205
  forAll genOnlineNode $ \node ->
1206
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1207
  let pdx = Node.idx node + 1
1208
      inst' = Instance.setPri inst pdx
1209
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1210
  in case Node.addSec node inst'' pdx of
1211
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1212
       _ -> failTest "Can't add instance"
1213

    
1214
testSuite "Node"
1215
            [ 'prop_Node_setAlias
1216
            , 'prop_Node_setOffline
1217
            , 'prop_Node_setMcpu
1218
            , 'prop_Node_setXmem
1219
            , 'prop_Node_addPriFM
1220
            , 'prop_Node_addPriFD
1221
            , 'prop_Node_addPriFC
1222
            , 'prop_Node_addSec
1223
            , 'prop_Node_addOfflinePri
1224
            , 'prop_Node_addOfflineSec
1225
            , 'prop_Node_rMem
1226
            , 'prop_Node_setMdsk
1227
            , 'prop_Node_tagMaps_idempotent
1228
            , 'prop_Node_tagMaps_reject
1229
            , 'prop_Node_showField
1230
            , 'prop_Node_computeGroups
1231
            , 'prop_Node_addPri_idempotent
1232
            , 'prop_Node_addSec_idempotent
1233
            ]
1234

    
1235
-- ** Cluster tests
1236

    
1237
-- | Check that the cluster score is close to zero for a homogeneous
1238
-- cluster.
1239
prop_Score_Zero :: Node.Node -> Property
1240
prop_Score_Zero node =
1241
  forAll (choose (1, 1024)) $ \count ->
1242
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1243
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1244
  let fn = Node.buildPeers node Container.empty
1245
      nlst = replicate count fn
1246
      score = Cluster.compCVNodes nlst
1247
  -- we can't say == 0 here as the floating point errors accumulate;
1248
  -- this should be much lower than the default score in CLI.hs
1249
  in score <= 1e-12
1250

    
1251
-- | Check that cluster stats are sane.
1252
prop_CStats_sane :: Property
1253
prop_CStats_sane =
1254
  forAll (choose (1, 1024)) $ \count ->
1255
  forAll genOnlineNode $ \node ->
1256
  let fn = Node.buildPeers node Container.empty
1257
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1258
      nl = Container.fromList nlst
1259
      cstats = Cluster.totalResources nl
1260
  in Cluster.csAdsk cstats >= 0 &&
1261
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1262

    
1263
-- | Check that one instance is allocated correctly, without
1264
-- rebalances needed.
1265
prop_ClusterAlloc_sane :: Instance.Instance -> Property
1266
prop_ClusterAlloc_sane inst =
1267
  forAll (choose (5, 20)) $ \count ->
1268
  forAll genOnlineNode $ \node ->
1269
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1270
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1271
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1272
     Cluster.tryAlloc nl il inst' of
1273
       Types.Bad _ -> False
1274
       Types.Ok as ->
1275
         case Cluster.asSolution as of
1276
           Nothing -> False
1277
           Just (xnl, xi, _, cv) ->
1278
             let il' = Container.add (Instance.idx xi) xi il
1279
                 tbl = Cluster.Table xnl il' cv []
1280
             in not (canBalance tbl True True False)
1281

    
1282
-- | Checks that on a 2-5 node cluster, we can allocate a random
1283
-- instance spec via tiered allocation (whatever the original instance
1284
-- spec), on either one or two nodes. Furthermore, we test that
1285
-- computed allocation statistics are correct.
1286
prop_ClusterCanTieredAlloc :: Instance.Instance -> Property
1287
prop_ClusterCanTieredAlloc inst =
1288
  forAll (choose (2, 5)) $ \count ->
1289
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1290
  let nl = makeSmallCluster node count
1291
      il = Container.empty
1292
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1293
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1294
  in case allocnodes >>= \allocnodes' ->
1295
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1296
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1297
       Types.Ok (_, nl', il', ixes, cstats) ->
1298
         let (ai_alloc, ai_pool, ai_unav) =
1299
               Cluster.computeAllocationDelta
1300
                (Cluster.totalResources nl)
1301
                (Cluster.totalResources nl')
1302
             all_nodes = Container.elems nl
1303
         in property (not (null ixes)) .&&.
1304
            IntMap.size il' ==? length ixes .&&.
1305
            length ixes ==? length cstats .&&.
1306
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1307
              sum (map Node.hiCpu all_nodes) .&&.
1308
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1309
              sum (map Node.tCpu all_nodes) .&&.
1310
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1311
              truncate (sum (map Node.tMem all_nodes)) .&&.
1312
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1313
              truncate (sum (map Node.tDsk all_nodes))
1314

    
1315
-- | Helper function to create a cluster with the given range of nodes
1316
-- and allocate an instance on it.
1317
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1318
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1319
genClusterAlloc count node inst =
1320
  let nl = makeSmallCluster node count
1321
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1322
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1323
     Cluster.tryAlloc nl Container.empty inst of
1324
       Types.Bad _ -> Types.Bad "Can't allocate"
1325
       Types.Ok as ->
1326
         case Cluster.asSolution as of
1327
           Nothing -> Types.Bad "Empty solution?"
1328
           Just (xnl, xi, _, _) ->
1329
             let xil = Container.add (Instance.idx xi) xi Container.empty
1330
             in Types.Ok (xnl, xil, xi)
1331

    
1332
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1333
-- we can also relocate it.
1334
prop_ClusterAllocRelocate :: Property
1335
prop_ClusterAllocRelocate =
1336
  forAll (choose (4, 8)) $ \count ->
1337
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1338
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1339
  case genClusterAlloc count node inst of
1340
    Types.Bad msg -> failTest msg
1341
    Types.Ok (nl, il, inst') ->
1342
      case IAlloc.processRelocate defGroupList nl il
1343
             (Instance.idx inst) 1
1344
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1345
                 then Instance.sNode
1346
                 else Instance.pNode) inst'] of
1347
        Types.Ok _ -> property True
1348
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1349

    
1350
-- | Helper property checker for the result of a nodeEvac or
1351
-- changeGroup operation.
1352
check_EvacMode :: Group.Group -> Instance.Instance
1353
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1354
               -> Property
1355
check_EvacMode grp inst result =
1356
  case result of
1357
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1358
    Types.Ok (_, _, es) ->
1359
      let moved = Cluster.esMoved es
1360
          failed = Cluster.esFailed es
1361
          opcodes = not . null $ Cluster.esOpCodes es
1362
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1363
         failmsg "'opcodes' is null" opcodes .&&.
1364
         case moved of
1365
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1366
                               .&&.
1367
                               failmsg "wrong target group"
1368
                                         (gdx == Group.idx grp)
1369
           v -> failmsg  ("invalid solution: " ++ show v) False
1370
  where failmsg :: String -> Bool -> Property
1371
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1372
        idx = Instance.idx inst
1373

    
1374
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1375
-- we can also node-evacuate it.
1376
prop_ClusterAllocEvacuate :: Property
1377
prop_ClusterAllocEvacuate =
1378
  forAll (choose (4, 8)) $ \count ->
1379
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1380
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1381
  case genClusterAlloc count node inst of
1382
    Types.Bad msg -> failTest msg
1383
    Types.Ok (nl, il, inst') ->
1384
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1385
                              Cluster.tryNodeEvac defGroupList nl il mode
1386
                                [Instance.idx inst']) .
1387
                              evacModeOptions .
1388
                              Instance.mirrorType $ inst'
1389

    
1390
-- | Checks that on a 4-8 node cluster with two node groups, once we
1391
-- allocate an instance on the first node group, we can also change
1392
-- its group.
1393
prop_ClusterAllocChangeGroup :: Property
1394
prop_ClusterAllocChangeGroup =
1395
  forAll (choose (4, 8)) $ \count ->
1396
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1397
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1398
  case genClusterAlloc count node inst of
1399
    Types.Bad msg -> failTest msg
1400
    Types.Ok (nl, il, inst') ->
1401
      -- we need to add a second node group and nodes to the cluster
1402
      let nl2 = Container.elems $ makeSmallCluster node count
1403
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1404
          maxndx = maximum . map Node.idx $ nl2
1405
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1406
                             , Node.idx = Node.idx n + maxndx }) nl2
1407
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1408
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1409
          nl' = IntMap.union nl nl4
1410
      in check_EvacMode grp2 inst' $
1411
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1412

    
1413
-- | Check that allocating multiple instances on a cluster, then
1414
-- adding an empty node, results in a valid rebalance.
1415
prop_ClusterAllocBalance :: Property
1416
prop_ClusterAllocBalance =
1417
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1418
  forAll (choose (3, 5)) $ \count ->
1419
  not (Node.offline node) && not (Node.failN1 node) ==>
1420
  let nl = makeSmallCluster node count
1421
      (hnode, nl') = IntMap.deleteFindMax nl
1422
      il = Container.empty
1423
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1424
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1425
  in case allocnodes >>= \allocnodes' ->
1426
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1427
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1428
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1429
       Types.Ok (_, xnl, il', _, _) ->
1430
         let ynl = Container.add (Node.idx hnode) hnode xnl
1431
             cv = Cluster.compCV ynl
1432
             tbl = Cluster.Table ynl il' cv []
1433
         in printTestCase "Failed to rebalance" $
1434
            canBalance tbl True True False
1435

    
1436
-- | Checks consistency.
1437
prop_ClusterCheckConsistency :: Node.Node -> Instance.Instance -> Bool
1438
prop_ClusterCheckConsistency node inst =
1439
  let nl = makeSmallCluster node 3
1440
      [node1, node2, node3] = Container.elems nl
1441
      node3' = node3 { Node.group = 1 }
1442
      nl' = Container.add (Node.idx node3') node3' nl
1443
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1444
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1445
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1446
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1447
  in null (ccheck [(0, inst1)]) &&
1448
     null (ccheck [(0, inst2)]) &&
1449
     (not . null $ ccheck [(0, inst3)])
1450

    
1451
-- | For now, we only test that we don't lose instances during the split.
1452
prop_ClusterSplitCluster :: Node.Node -> Instance.Instance -> Property
1453
prop_ClusterSplitCluster node inst =
1454
  forAll (choose (0, 100)) $ \icnt ->
1455
  let nl = makeSmallCluster node 2
1456
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1457
                   (nl, Container.empty) [1..icnt]
1458
      gni = Cluster.splitCluster nl' il'
1459
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1460
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1461
                                 (Container.elems nl'')) gni
1462

    
1463
-- | Helper function to check if we can allocate an instance on a
1464
-- given node list.
1465
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1466
canAllocOn nl reqnodes inst =
1467
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1468
       Cluster.tryAlloc nl (Container.empty) inst of
1469
       Types.Bad _ -> False
1470
       Types.Ok as ->
1471
         case Cluster.asSolution as of
1472
           Nothing -> False
1473
           Just _ -> True
1474

    
1475
-- | Checks that allocation obeys minimum and maximum instance
1476
-- policies. The unittest generates a random node, duplicates it /count/
1477
-- times, and generates a random instance that can be allocated on
1478
-- this mini-cluster; it then checks that after applying a policy that
1479
-- the instance doesn't fits, the allocation fails.
1480
prop_ClusterAllocPolicy :: Node.Node -> Property
1481
prop_ClusterAllocPolicy node =
1482
  -- rqn is the required nodes (1 or 2)
1483
  forAll (choose (1, 2)) $ \rqn ->
1484
  forAll (choose (5, 20)) $ \count ->
1485
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1486
         $ \inst ->
1487
  forAll (arbitrary `suchThat` (isFailure .
1488
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1489
  let node' = Node.setPolicy ipol node
1490
      nl = makeSmallCluster node' count
1491
  in not $ canAllocOn nl rqn inst
1492

    
1493
testSuite "Cluster"
1494
            [ 'prop_Score_Zero
1495
            , 'prop_CStats_sane
1496
            , 'prop_ClusterAlloc_sane
1497
            , 'prop_ClusterCanTieredAlloc
1498
            , 'prop_ClusterAllocRelocate
1499
            , 'prop_ClusterAllocEvacuate
1500
            , 'prop_ClusterAllocChangeGroup
1501
            , 'prop_ClusterAllocBalance
1502
            , 'prop_ClusterCheckConsistency
1503
            , 'prop_ClusterSplitCluster
1504
            , 'prop_ClusterAllocPolicy
1505
            ]
1506

    
1507
-- ** OpCodes tests
1508

    
1509
-- | Check that opcode serialization is idempotent.
1510
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1511
prop_OpCodes_serialization op =
1512
  case J.readJSON (J.showJSON op) of
1513
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1514
    J.Ok op' -> op ==? op'
1515

    
1516
testSuite "OpCodes"
1517
            [ 'prop_OpCodes_serialization ]
1518

    
1519
-- ** Jobs tests
1520

    
1521
-- | Check that (queued) job\/opcode status serialization is idempotent.
1522
prop_OpStatus_serialization :: Jobs.OpStatus -> Property
1523
prop_OpStatus_serialization os =
1524
  case J.readJSON (J.showJSON os) of
1525
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1526
    J.Ok os' -> os ==? os'
1527

    
1528
prop_JobStatus_serialization :: Jobs.JobStatus -> Property
1529
prop_JobStatus_serialization js =
1530
  case J.readJSON (J.showJSON js) of
1531
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1532
    J.Ok js' -> js ==? js'
1533

    
1534
testSuite "Jobs"
1535
            [ 'prop_OpStatus_serialization
1536
            , 'prop_JobStatus_serialization
1537
            ]
1538

    
1539
-- ** Loader tests
1540

    
1541
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1542
prop_Loader_lookupNode ktn inst node =
1543
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1544
    where nl = Data.Map.fromList ktn
1545

    
1546
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1547
prop_Loader_lookupInstance kti inst =
1548
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1549
    where il = Data.Map.fromList kti
1550

    
1551
prop_Loader_assignIndices :: Property
1552
prop_Loader_assignIndices =
1553
  -- generate nodes with unique names
1554
  forAll (arbitrary `suchThat`
1555
          (\nodes ->
1556
             let names = map Node.name nodes
1557
             in length names == length (nub names))) $ \nodes ->
1558
  let (nassoc, kt) =
1559
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1560
  in Data.Map.size nassoc == length nodes &&
1561
     Container.size kt == length nodes &&
1562
     if not (null nodes)
1563
       then maximum (IntMap.keys kt) == length nodes - 1
1564
       else True
1565

    
1566
-- | Checks that the number of primary instances recorded on the nodes
1567
-- is zero.
1568
prop_Loader_mergeData :: [Node.Node] -> Bool
1569
prop_Loader_mergeData ns =
1570
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1571
  in case Loader.mergeData [] [] [] []
1572
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1573
    Types.Bad _ -> False
1574
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1575
      let nodes = Container.elems nl
1576
          instances = Container.elems il
1577
      in (sum . map (length . Node.pList)) nodes == 0 &&
1578
         null instances
1579

    
1580
-- | Check that compareNameComponent on equal strings works.
1581
prop_Loader_compareNameComponent_equal :: String -> Bool
1582
prop_Loader_compareNameComponent_equal s =
1583
  Loader.compareNameComponent s s ==
1584
    Loader.LookupResult Loader.ExactMatch s
1585

    
1586
-- | Check that compareNameComponent on prefix strings works.
1587
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1588
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1589
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1590
    Loader.LookupResult Loader.PartialMatch s1
1591

    
1592
testSuite "Loader"
1593
            [ 'prop_Loader_lookupNode
1594
            , 'prop_Loader_lookupInstance
1595
            , 'prop_Loader_assignIndices
1596
            , 'prop_Loader_mergeData
1597
            , 'prop_Loader_compareNameComponent_equal
1598
            , 'prop_Loader_compareNameComponent_prefix
1599
            ]
1600

    
1601
-- ** Types tests
1602

    
1603
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1604
prop_Types_AllocPolicy_serialisation apol =
1605
  case J.readJSON (J.showJSON apol) of
1606
    J.Ok p -> p ==? apol
1607
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1608

    
1609
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1610
prop_Types_DiskTemplate_serialisation dt =
1611
  case J.readJSON (J.showJSON dt) of
1612
    J.Ok p -> p ==? dt
1613
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1614

    
1615
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1616
prop_Types_ISpec_serialisation ispec =
1617
  case J.readJSON (J.showJSON ispec) of
1618
    J.Ok p -> p ==? ispec
1619
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1620

    
1621
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1622
prop_Types_IPolicy_serialisation ipol =
1623
  case J.readJSON (J.showJSON ipol) of
1624
    J.Ok p -> p ==? ipol
1625
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1626

    
1627
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1628
prop_Types_EvacMode_serialisation em =
1629
  case J.readJSON (J.showJSON em) of
1630
    J.Ok p -> p ==? em
1631
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1632

    
1633
prop_Types_opToResult :: Types.OpResult Int -> Bool
1634
prop_Types_opToResult op =
1635
  case op of
1636
    Types.OpFail _ -> Types.isBad r
1637
    Types.OpGood v -> case r of
1638
                        Types.Bad _ -> False
1639
                        Types.Ok v' -> v == v'
1640
  where r = Types.opToResult op
1641

    
1642
prop_Types_eitherToResult :: Either String Int -> Bool
1643
prop_Types_eitherToResult ei =
1644
  case ei of
1645
    Left _ -> Types.isBad r
1646
    Right v -> case r of
1647
                 Types.Bad _ -> False
1648
                 Types.Ok v' -> v == v'
1649
    where r = Types.eitherToResult ei
1650

    
1651
testSuite "Types"
1652
            [ 'prop_Types_AllocPolicy_serialisation
1653
            , 'prop_Types_DiskTemplate_serialisation
1654
            , 'prop_Types_ISpec_serialisation
1655
            , 'prop_Types_IPolicy_serialisation
1656
            , 'prop_Types_EvacMode_serialisation
1657
            , 'prop_Types_opToResult
1658
            , 'prop_Types_eitherToResult
1659
            ]
1660

    
1661
-- ** CLI tests
1662

    
1663
-- | Test correct parsing.
1664
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1665
prop_CLI_parseISpec descr dsk mem cpu =
1666
  let str = printf "%d,%d,%d" dsk mem cpu::String
1667
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1668

    
1669
-- | Test parsing failure due to wrong section count.
1670
prop_CLI_parseISpecFail :: String -> Property
1671
prop_CLI_parseISpecFail descr =
1672
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1673
  forAll (replicateM nelems arbitrary) $ \values ->
1674
  let str = intercalate "," $ map show (values::[Int])
1675
  in case CLI.parseISpecString descr str of
1676
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1677
       _ -> property True
1678

    
1679
-- | Test parseYesNo.
1680
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1681
prop_CLI_parseYesNo def testval val =
1682
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1683
  if testval
1684
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1685
    else let result = CLI.parseYesNo def (Just actual_val)
1686
         in if actual_val `elem` ["yes", "no"]
1687
              then result ==? Types.Ok (actual_val == "yes")
1688
              else property $ Types.isBad result
1689

    
1690
-- | Helper to check for correct parsing of string arg.
1691
checkStringArg :: [Char]
1692
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1693
                   CLI.Options -> Maybe [Char])
1694
               -> Property
1695
checkStringArg val (opt, fn) =
1696
  let GetOpt.Option _ longs _ _ = opt
1697
  in case longs of
1698
       [] -> failTest "no long options?"
1699
       cmdarg:_ ->
1700
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1701
           Left e -> failTest $ "Failed to parse option: " ++ show e
1702
           Right (options, _) -> fn options ==? Just val
1703

    
1704
-- | Test a few string arguments.
1705
prop_CLI_StringArg :: [Char] -> Property
1706
prop_CLI_StringArg argument =
1707
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1708
             , (CLI.oDynuFile,      CLI.optDynuFile)
1709
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1710
             , (CLI.oReplay,        CLI.optReplay)
1711
             , (CLI.oPrintCommands, CLI.optShowCmds)
1712
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1713
             ]
1714
  in conjoin $ map (checkStringArg argument) args
1715

    
1716
-- | Helper to test that a given option is accepted OK with quick exit.
1717
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1718
checkEarlyExit name options param =
1719
  case CLI.parseOptsInner [param] name options of
1720
    Left (code, _) -> if code == 0
1721
                          then property True
1722
                          else failTest $ "Program " ++ name ++
1723
                                 " returns invalid code " ++ show code ++
1724
                                 " for option " ++ param
1725
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1726
         param ++ " as early exit one"
1727

    
1728
-- | Test that all binaries support some common options. There is
1729
-- nothing actually random about this test...
1730
prop_CLI_stdopts :: Property
1731
prop_CLI_stdopts =
1732
  let params = ["-h", "--help", "-V", "--version"]
1733
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1734
      -- apply checkEarlyExit across the cartesian product of params and opts
1735
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1736

    
1737
testSuite "CLI"
1738
          [ 'prop_CLI_parseISpec
1739
          , 'prop_CLI_parseISpecFail
1740
          , 'prop_CLI_parseYesNo
1741
          , 'prop_CLI_StringArg
1742
          , 'prop_CLI_stdopts
1743
          ]
1744

    
1745
-- * JSON tests
1746

    
1747
prop_JSON_toArray :: [Int] -> Property
1748
prop_JSON_toArray intarr =
1749
  let arr = map J.showJSON intarr in
1750
  case JSON.toArray (J.JSArray arr) of
1751
    Types.Ok arr' -> arr ==? arr'
1752
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1753

    
1754
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1755
prop_JSON_toArrayFail i s b =
1756
  -- poor man's instance Arbitrary JSValue
1757
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1758
  case JSON.toArray item of
1759
    Types.Bad _ -> property True
1760
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1761

    
1762
testSuite "JSON"
1763
          [ 'prop_JSON_toArray
1764
          , 'prop_JSON_toArrayFail
1765
          ]
1766

    
1767
-- * Luxi tests
1768

    
1769
instance Arbitrary Luxi.LuxiReq where
1770
  arbitrary = elements [minBound..maxBound]
1771

    
1772
instance Arbitrary Luxi.QrViaLuxi where
1773
  arbitrary = elements [minBound..maxBound]
1774

    
1775
instance Arbitrary Luxi.LuxiOp where
1776
  arbitrary = do
1777
    lreq <- arbitrary
1778
    case lreq of
1779
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> arbitrary
1780
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1781
                            getFields <*> arbitrary
1782
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1783
                             arbitrary <*> arbitrary
1784
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1785
                                getFields <*> arbitrary
1786
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1787
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1788
                              (listOf getFQDN) <*> arbitrary
1789
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1790
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1791
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> getName <*> getFQDN
1792
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1793
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1794
                                (resize maxOpCodes arbitrary)
1795
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1796
                                  getFields <*> pure J.JSNull <*>
1797
                                  pure J.JSNull <*> arbitrary
1798
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1799
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1800
                                 arbitrary
1801
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1802
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1803
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1804

    
1805
-- | Simple check that encoding/decoding of LuxiOp works.
1806
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1807
prop_Luxi_CallEncoding op =
1808
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1809

    
1810
testSuite "LUXI"
1811
          [ 'prop_Luxi_CallEncoding
1812
          ]
1813

    
1814
-- * Ssconf tests
1815

    
1816
instance Arbitrary Ssconf.SSKey where
1817
  arbitrary = elements [minBound..maxBound]
1818

    
1819
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1820
prop_Ssconf_filename key =
1821
  printTestCase "Key doesn't start with correct prefix" $
1822
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1823

    
1824
testSuite "Ssconf"
1825
  [ 'prop_Ssconf_filename
1826
  ]