Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (73.1 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 Test.QuickCheck.Monadic (assert, monadicIO, run)
55
import Text.Printf (printf)
56
import Data.List (intercalate, nub, isPrefixOf)
57
import Data.Maybe
58
import Control.Monad
59
import Control.Applicative
60
import qualified System.Console.GetOpt as GetOpt
61
import qualified Text.JSON as J
62
import qualified Data.Map
63
import qualified Data.IntMap as IntMap
64
import Control.Concurrent (forkIO)
65
import Control.Exception (bracket, catchJust)
66
import System.Directory (getTemporaryDirectory, removeFile)
67
import System.IO (hClose, openTempFile)
68
import System.IO.Error (isEOFErrorType, ioeGetErrorType)
69

    
70
import qualified Ganeti.Confd as Confd
71
import qualified Ganeti.Config as Config
72
import qualified Ganeti.Daemon as Daemon
73
import qualified Ganeti.Hash as Hash
74
import qualified Ganeti.BasicTypes as BasicTypes
75
import qualified Ganeti.Jobs as Jobs
76
import qualified Ganeti.Logging as Logging
77
import qualified Ganeti.Luxi as Luxi
78
import qualified Ganeti.Objects as Objects
79
import qualified Ganeti.OpCodes as OpCodes
80
import qualified Ganeti.Query2 as Query2
81
import qualified Ganeti.Rpc as Rpc
82
import qualified Ganeti.Runtime as Runtime
83
import qualified Ganeti.Ssconf as Ssconf
84
import qualified Ganeti.HTools.CLI as CLI
85
import qualified Ganeti.HTools.Cluster as Cluster
86
import qualified Ganeti.HTools.Container as Container
87
import qualified Ganeti.HTools.ExtLoader
88
import qualified Ganeti.HTools.Group as Group
89
import qualified Ganeti.HTools.IAlloc as IAlloc
90
import qualified Ganeti.HTools.Instance as Instance
91
import qualified Ganeti.HTools.JSON as JSON
92
import qualified Ganeti.HTools.Loader as Loader
93
import qualified Ganeti.HTools.Luxi as HTools.Luxi
94
import qualified Ganeti.HTools.Node as Node
95
import qualified Ganeti.HTools.PeerMap as PeerMap
96
import qualified Ganeti.HTools.Rapi
97
import qualified Ganeti.HTools.Simu as Simu
98
import qualified Ganeti.HTools.Text as Text
99
import qualified Ganeti.HTools.Types as Types
100
import qualified Ganeti.HTools.Utils as Utils
101
import qualified Ganeti.HTools.Version
102
import qualified Ganeti.Constants as C
103

    
104
import qualified Ganeti.HTools.Program as Program
105
import qualified Ganeti.HTools.Program.Hail
106
import qualified Ganeti.HTools.Program.Hbal
107
import qualified Ganeti.HTools.Program.Hscan
108
import qualified Ganeti.HTools.Program.Hspace
109

    
110
import Ganeti.HTools.QCHelper (testSuite)
111

    
112
-- * Constants
113

    
114
-- | Maximum memory (1TiB, somewhat random value).
115
maxMem :: Int
116
maxMem = 1024 * 1024
117

    
118
-- | Maximum disk (8TiB, somewhat random value).
119
maxDsk :: Int
120
maxDsk = 1024 * 1024 * 8
121

    
122
-- | Max CPUs (1024, somewhat random value).
123
maxCpu :: Int
124
maxCpu = 1024
125

    
126
-- | Max vcpu ratio (random value).
127
maxVcpuRatio :: Double
128
maxVcpuRatio = 1024.0
129

    
130
-- | Max spindle ratio (random value).
131
maxSpindleRatio :: Double
132
maxSpindleRatio = 1024.0
133

    
134
-- | Max nodes, used just to limit arbitrary instances for smaller
135
-- opcode definitions (e.g. list of nodes in OpTestDelay).
136
maxNodes :: Int
137
maxNodes = 32
138

    
139
-- | Max opcodes or jobs in a submit job and submit many jobs.
140
maxOpCodes :: Int
141
maxOpCodes = 16
142

    
143
-- | All disk templates (used later)
144
allDiskTemplates :: [Types.DiskTemplate]
145
allDiskTemplates = [minBound..maxBound]
146

    
147
-- | Null iPolicy, and by null we mean very liberal.
148
nullIPolicy :: Types.IPolicy
149
nullIPolicy = Types.IPolicy
150
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
151
                                       , Types.iSpecCpuCount   = 0
152
                                       , Types.iSpecDiskSize   = 0
153
                                       , Types.iSpecDiskCount  = 0
154
                                       , Types.iSpecNicCount   = 0
155
                                       , Types.iSpecSpindleUse = 0
156
                                       }
157
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
158
                                       , Types.iSpecCpuCount   = maxBound
159
                                       , Types.iSpecDiskSize   = maxBound
160
                                       , Types.iSpecDiskCount  = C.maxDisks
161
                                       , Types.iSpecNicCount   = C.maxNics
162
                                       , Types.iSpecSpindleUse = maxBound
163
                                       }
164
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
165
                                       , Types.iSpecCpuCount   = Types.unitCpu
166
                                       , Types.iSpecDiskSize   = Types.unitDsk
167
                                       , Types.iSpecDiskCount  = 1
168
                                       , Types.iSpecNicCount   = 1
169
                                       , Types.iSpecSpindleUse = 1
170
                                       }
171
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
172
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
173
                                          -- enough to not impact us
174
  , Types.iPolicySpindleRatio = maxSpindleRatio
175
  }
176

    
177

    
178
defGroup :: Group.Group
179
defGroup = flip Group.setIdx 0 $
180
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
181
                  nullIPolicy
182

    
183
defGroupList :: Group.List
184
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
185

    
186
defGroupAssoc :: Data.Map.Map String Types.Gdx
187
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
188

    
189
-- * Helper functions
190

    
191
-- | Simple checker for whether OpResult is fail or pass.
192
isFailure :: Types.OpResult a -> Bool
193
isFailure (Types.OpFail _) = True
194
isFailure _ = False
195

    
196
-- | Checks for equality with proper annotation.
197
(==?) :: (Show a, Eq a) => a -> a -> Property
198
(==?) x y = printTestCase
199
            ("Expected equality, but '" ++
200
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
201
infix 3 ==?
202

    
203
-- | Show a message and fail the test.
204
failTest :: String -> Property
205
failTest msg = printTestCase msg False
206

    
207
-- | Update an instance to be smaller than a node.
208
setInstanceSmallerThanNode :: Node.Node
209
                           -> Instance.Instance -> Instance.Instance
210
setInstanceSmallerThanNode node inst =
211
  inst { Instance.mem = Node.availMem node `div` 2
212
       , Instance.dsk = Node.availDisk node `div` 2
213
       , Instance.vcpus = Node.availCpu node `div` 2
214
       }
215

    
216
-- | Create an instance given its spec.
217
createInstance :: Int -> Int -> Int -> Instance.Instance
218
createInstance mem dsk vcpus =
219
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
220
    Types.DTDrbd8 1
221

    
222
-- | Create a small cluster by repeating a node spec.
223
makeSmallCluster :: Node.Node -> Int -> Node.List
224
makeSmallCluster node count =
225
  let origname = Node.name node
226
      origalias = Node.alias node
227
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
228
                                , Node.alias = origalias ++ "-" ++ show idx })
229
              [1..count]
230
      fn = flip Node.buildPeers Container.empty
231
      namelst = map (\n -> (Node.name n, fn n)) nodes
232
      (_, nlst) = Loader.assignIndices namelst
233
  in nlst
234

    
235
-- | Make a small cluster, both nodes and instances.
236
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
237
                      -> (Node.List, Instance.List, Instance.Instance)
238
makeSmallEmptyCluster node count inst =
239
  (makeSmallCluster node count, Container.empty,
240
   setInstanceSmallerThanNode node inst)
241

    
242
-- | Checks if a node is "big" enough.
243
isNodeBig :: Int -> Node.Node -> Bool
244
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
245
                      && Node.availMem node > size * Types.unitMem
246
                      && Node.availCpu node > size * Types.unitCpu
247

    
248
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
249
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
250

    
251
-- | Assigns a new fresh instance to a cluster; this is not
252
-- allocation, so no resource checks are done.
253
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
254
                  Types.Idx -> Types.Idx ->
255
                  (Node.List, Instance.List)
256
assignInstance nl il inst pdx sdx =
257
  let pnode = Container.find pdx nl
258
      snode = Container.find sdx nl
259
      maxiidx = if Container.null il
260
                  then 0
261
                  else fst (Container.findMax il) + 1
262
      inst' = inst { Instance.idx = maxiidx,
263
                     Instance.pNode = pdx, Instance.sNode = sdx }
264
      pnode' = Node.setPri pnode inst'
265
      snode' = Node.setSec snode inst'
266
      nl' = Container.addTwo pdx pnode' sdx snode' nl
267
      il' = Container.add maxiidx inst' il
268
  in (nl', il')
269

    
270
-- | Generates a list of a given size with non-duplicate elements.
271
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
272
genUniquesList cnt =
273
  foldM (\lst _ -> do
274
           newelem <- arbitrary `suchThat` (`notElem` lst)
275
           return (newelem:lst)) [] [1..cnt]
276

    
277
-- | Checks if an instance is mirrored.
278
isMirrored :: Instance.Instance -> Bool
279
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
280

    
281
-- | Returns the possible change node types for a disk template.
282
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
283
evacModeOptions Types.MirrorNone     = []
284
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
285
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
286

    
287
-- * Arbitrary instances
288

    
289
-- | Defines a DNS name.
290
newtype DNSChar = DNSChar { dnsGetChar::Char }
291

    
292
instance Arbitrary DNSChar where
293
  arbitrary = do
294
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
295
    return (DNSChar x)
296

    
297
instance Show DNSChar where
298
  show = show . dnsGetChar
299

    
300
-- | Generates a single name component.
301
getName :: Gen String
302
getName = do
303
  n <- choose (1, 64)
304
  dn <- vector n
305
  return (map dnsGetChar dn)
306

    
307
-- | Generates an entire FQDN.
308
getFQDN :: Gen String
309
getFQDN = do
310
  ncomps <- choose (1, 4)
311
  names <- vectorOf ncomps getName
312
  return $ intercalate "." names
313

    
314
-- | Combinator that generates a 'Maybe' using a sub-combinator.
315
getMaybe :: Gen a -> Gen (Maybe a)
316
getMaybe subgen = do
317
  bool <- arbitrary
318
  if bool
319
    then Just <$> subgen
320
    else return Nothing
321

    
322
-- | Generates a fields list. This uses the same character set as a
323
-- DNS name (just for simplicity).
324
getFields :: Gen [String]
325
getFields = do
326
  n <- choose (1, 32)
327
  vectorOf n getName
328

    
329
-- | Defines a tag type.
330
newtype TagChar = TagChar { tagGetChar :: Char }
331

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

    
337
instance Arbitrary TagChar where
338
  arbitrary = do
339
    c <- elements tagChar
340
    return (TagChar c)
341

    
342
-- | Generates a tag
343
genTag :: Gen [TagChar]
344
genTag = do
345
  -- the correct value would be C.maxTagLen, but that's way too
346
  -- verbose in unittests, and at the moment I don't see any possible
347
  -- bugs with longer tags and the way we use tags in htools
348
  n <- choose (1, 10)
349
  vector n
350

    
351
-- | Generates a list of tags (correctly upper bounded).
352
genTags :: Gen [String]
353
genTags = do
354
  -- the correct value would be C.maxTagsPerObj, but per the comment
355
  -- in genTag, we don't use tags enough in htools to warrant testing
356
  -- such big values
357
  n <- choose (0, 10::Int)
358
  tags <- mapM (const genTag) [1..n]
359
  return $ map (map tagGetChar) tags
360

    
361
instance Arbitrary Types.InstanceStatus where
362
    arbitrary = elements [minBound..maxBound]
363

    
364
-- | Generates a random instance with maximum disk/mem/cpu values.
365
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
366
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
367
  name <- getFQDN
368
  mem <- choose (0, lim_mem)
369
  dsk <- choose (0, lim_dsk)
370
  run_st <- arbitrary
371
  pn <- arbitrary
372
  sn <- arbitrary
373
  vcpus <- choose (0, lim_cpu)
374
  dt <- arbitrary
375
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
376

    
377
-- | Generates an instance smaller than a node.
378
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
379
genInstanceSmallerThanNode node =
380
  genInstanceSmallerThan (Node.availMem node `div` 2)
381
                         (Node.availDisk node `div` 2)
382
                         (Node.availCpu node `div` 2)
383

    
384
-- let's generate a random instance
385
instance Arbitrary Instance.Instance where
386
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
387

    
388
-- | Generas an arbitrary node based on sizing information.
389
genNode :: Maybe Int -- ^ Minimum node size in terms of units
390
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
391
                     -- just by the max... constants)
392
        -> Gen Node.Node
393
genNode min_multiplier max_multiplier = do
394
  let (base_mem, base_dsk, base_cpu) =
395
        case min_multiplier of
396
          Just mm -> (mm * Types.unitMem,
397
                      mm * Types.unitDsk,
398
                      mm * Types.unitCpu)
399
          Nothing -> (0, 0, 0)
400
      (top_mem, top_dsk, top_cpu)  =
401
        case max_multiplier of
402
          Just mm -> (mm * Types.unitMem,
403
                      mm * Types.unitDsk,
404
                      mm * Types.unitCpu)
405
          Nothing -> (maxMem, maxDsk, maxCpu)
406
  name  <- getFQDN
407
  mem_t <- choose (base_mem, top_mem)
408
  mem_f <- choose (base_mem, mem_t)
409
  mem_n <- choose (0, mem_t - mem_f)
410
  dsk_t <- choose (base_dsk, top_dsk)
411
  dsk_f <- choose (base_dsk, dsk_t)
412
  cpu_t <- choose (base_cpu, top_cpu)
413
  offl  <- arbitrary
414
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
415
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
416
      n' = Node.setPolicy nullIPolicy n
417
  return $ Node.buildPeers n' Container.empty
418

    
419
-- | Helper function to generate a sane node.
420
genOnlineNode :: Gen Node.Node
421
genOnlineNode = do
422
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
423
                              not (Node.failN1 n) &&
424
                              Node.availDisk n > 0 &&
425
                              Node.availMem n > 0 &&
426
                              Node.availCpu n > 0)
427

    
428
-- and a random node
429
instance Arbitrary Node.Node where
430
  arbitrary = genNode Nothing Nothing
431

    
432
-- replace disks
433
instance Arbitrary OpCodes.ReplaceDisksMode where
434
  arbitrary = elements [minBound..maxBound]
435

    
436
instance Arbitrary OpCodes.OpCode where
437
  arbitrary = do
438
    op_id <- elements [ "OP_TEST_DELAY"
439
                      , "OP_INSTANCE_REPLACE_DISKS"
440
                      , "OP_INSTANCE_FAILOVER"
441
                      , "OP_INSTANCE_MIGRATE"
442
                      ]
443
    case op_id of
444
      "OP_TEST_DELAY" ->
445
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
446
                 <*> resize maxNodes (listOf getFQDN)
447
      "OP_INSTANCE_REPLACE_DISKS" ->
448
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
449
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
450
      "OP_INSTANCE_FAILOVER" ->
451
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
452
          getMaybe getFQDN
453
      "OP_INSTANCE_MIGRATE" ->
454
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
455
          arbitrary <*> arbitrary <*> getMaybe getFQDN
456
      _ -> fail "Wrong opcode"
457

    
458
instance Arbitrary Jobs.OpStatus where
459
  arbitrary = elements [minBound..maxBound]
460

    
461
instance Arbitrary Jobs.JobStatus where
462
  arbitrary = elements [minBound..maxBound]
463

    
464
newtype SmallRatio = SmallRatio Double deriving Show
465
instance Arbitrary SmallRatio where
466
  arbitrary = do
467
    v <- choose (0, 1)
468
    return $ SmallRatio v
469

    
470
instance Arbitrary Types.AllocPolicy where
471
  arbitrary = elements [minBound..maxBound]
472

    
473
instance Arbitrary Types.DiskTemplate where
474
  arbitrary = elements [minBound..maxBound]
475

    
476
instance Arbitrary Types.FailMode where
477
  arbitrary = elements [minBound..maxBound]
478

    
479
instance Arbitrary Types.EvacMode where
480
  arbitrary = elements [minBound..maxBound]
481

    
482
instance Arbitrary a => Arbitrary (Types.OpResult a) where
483
  arbitrary = arbitrary >>= \c ->
484
              if c
485
                then Types.OpGood <$> arbitrary
486
                else Types.OpFail <$> arbitrary
487

    
488
instance Arbitrary Types.ISpec where
489
  arbitrary = do
490
    mem_s <- arbitrary::Gen (NonNegative Int)
491
    dsk_c <- arbitrary::Gen (NonNegative Int)
492
    dsk_s <- arbitrary::Gen (NonNegative Int)
493
    cpu_c <- arbitrary::Gen (NonNegative Int)
494
    nic_c <- arbitrary::Gen (NonNegative Int)
495
    su    <- arbitrary::Gen (NonNegative Int)
496
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
497
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
498
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
499
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
500
                       , Types.iSpecNicCount   = fromIntegral nic_c
501
                       , Types.iSpecSpindleUse = fromIntegral su
502
                       }
503

    
504
-- | Generates an ispec bigger than the given one.
505
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
506
genBiggerISpec imin = do
507
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
508
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
509
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
510
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
511
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
512
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
513
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
514
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
515
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
516
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
517
                     , Types.iSpecNicCount   = fromIntegral nic_c
518
                     , Types.iSpecSpindleUse = fromIntegral su
519
                     }
520

    
521
instance Arbitrary Types.IPolicy where
522
  arbitrary = do
523
    imin <- arbitrary
524
    istd <- genBiggerISpec imin
525
    imax <- genBiggerISpec istd
526
    num_tmpl <- choose (0, length allDiskTemplates)
527
    dts  <- genUniquesList num_tmpl
528
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
529
    spindle_ratio <- choose (1.0, maxSpindleRatio)
530
    return Types.IPolicy { Types.iPolicyMinSpec = imin
531
                         , Types.iPolicyStdSpec = istd
532
                         , Types.iPolicyMaxSpec = imax
533
                         , Types.iPolicyDiskTemplates = dts
534
                         , Types.iPolicyVcpuRatio = vcpu_ratio
535
                         , Types.iPolicySpindleRatio = spindle_ratio
536
                         }
537

    
538
-- * Actual tests
539

    
540
-- ** Utils tests
541

    
542
-- | Helper to generate a small string that doesn't contain commas.
543
genNonCommaString :: Gen [Char]
544
genNonCommaString = do
545
  size <- choose (0, 20) -- arbitrary max size
546
  vectorOf size (arbitrary `suchThat` ((/=) ','))
547

    
548
-- | If the list is not just an empty element, and if the elements do
549
-- not contain commas, then join+split should be idempotent.
550
prop_Utils_commaJoinSplit :: Property
551
prop_Utils_commaJoinSplit =
552
  forAll (choose (0, 20)) $ \llen ->
553
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
554
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
555

    
556
-- | Split and join should always be idempotent.
557
prop_Utils_commaSplitJoin :: [Char] -> Property
558
prop_Utils_commaSplitJoin s =
559
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
560

    
561
-- | fromObjWithDefault, we test using the Maybe monad and an integer
562
-- value.
563
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
564
prop_Utils_fromObjWithDefault def_value random_key =
565
  -- a missing key will be returned with the default
566
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
567
  -- a found key will be returned as is, not with default
568
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
569
       random_key (def_value+1) == Just def_value
570

    
571
-- | Test that functional if' behaves like the syntactic sugar if.
572
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
573
prop_Utils_if'if cnd a b =
574
  Utils.if' cnd a b ==? if cnd then a else b
575

    
576
-- | Test basic select functionality
577
prop_Utils_select :: Int      -- ^ Default result
578
                  -> [Int]    -- ^ List of False values
579
                  -> [Int]    -- ^ List of True values
580
                  -> Gen Prop -- ^ Test result
581
prop_Utils_select def lst1 lst2 =
582
  Utils.select def (flist ++ tlist) ==? expectedresult
583
    where expectedresult = Utils.if' (null lst2) def (head lst2)
584
          flist = zip (repeat False) lst1
585
          tlist = zip (repeat True)  lst2
586

    
587
-- | Test basic select functionality with undefined default
588
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
589
                         -> NonEmptyList Int -- ^ List of True values
590
                         -> Gen Prop         -- ^ Test result
591
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
592
  Utils.select undefined (flist ++ tlist) ==? head lst2
593
    where flist = zip (repeat False) lst1
594
          tlist = zip (repeat True)  lst2
595

    
596
-- | Test basic select functionality with undefined list values
597
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
598
                         -> NonEmptyList Int -- ^ List of True values
599
                         -> Gen Prop         -- ^ Test result
600
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
601
  Utils.select undefined cndlist ==? head lst2
602
    where flist = zip (repeat False) lst1
603
          tlist = zip (repeat True)  lst2
604
          cndlist = flist ++ tlist ++ [undefined]
605

    
606
prop_Utils_parseUnit :: NonNegative Int -> Property
607
prop_Utils_parseUnit (NonNegative n) =
608
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
609
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
610
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
611
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
612
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
613
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
614
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
615
  printTestCase "Internal error/overflow?"
616
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
617
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
618
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
619
        n_gb = n_mb * 1000
620
        n_tb = n_gb * 1000
621

    
622
-- | Test list for the Utils module.
623
testSuite "Utils"
624
            [ 'prop_Utils_commaJoinSplit
625
            , 'prop_Utils_commaSplitJoin
626
            , 'prop_Utils_fromObjWithDefault
627
            , 'prop_Utils_if'if
628
            , 'prop_Utils_select
629
            , 'prop_Utils_select_undefd
630
            , 'prop_Utils_select_undefv
631
            , 'prop_Utils_parseUnit
632
            ]
633

    
634
-- ** PeerMap tests
635

    
636
-- | Make sure add is idempotent.
637
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
638
                           -> PeerMap.Key -> PeerMap.Elem -> Property
639
prop_PeerMap_addIdempotent pmap key em =
640
  fn puniq ==? fn (fn puniq)
641
    where fn = PeerMap.add key em
642
          puniq = PeerMap.accumArray const pmap
643

    
644
-- | Make sure remove is idempotent.
645
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
646
prop_PeerMap_removeIdempotent pmap key =
647
  fn puniq ==? fn (fn puniq)
648
    where fn = PeerMap.remove key
649
          puniq = PeerMap.accumArray const pmap
650

    
651
-- | Make sure a missing item returns 0.
652
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
653
prop_PeerMap_findMissing pmap key =
654
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
655
    where puniq = PeerMap.accumArray const pmap
656

    
657
-- | Make sure an added item is found.
658
prop_PeerMap_addFind :: PeerMap.PeerMap
659
                     -> PeerMap.Key -> PeerMap.Elem -> Property
660
prop_PeerMap_addFind pmap key em =
661
  PeerMap.find key (PeerMap.add key em puniq) ==? em
662
    where puniq = PeerMap.accumArray const pmap
663

    
664
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
665
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
666
prop_PeerMap_maxElem pmap =
667
  PeerMap.maxElem puniq ==? if null puniq then 0
668
                              else (maximum . snd . unzip) puniq
669
    where puniq = PeerMap.accumArray const pmap
670

    
671
-- | List of tests for the PeerMap module.
672
testSuite "PeerMap"
673
            [ 'prop_PeerMap_addIdempotent
674
            , 'prop_PeerMap_removeIdempotent
675
            , 'prop_PeerMap_maxElem
676
            , 'prop_PeerMap_addFind
677
            , 'prop_PeerMap_findMissing
678
            ]
679

    
680
-- ** Container tests
681

    
682
-- we silence the following due to hlint bug fixed in later versions
683
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
684
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
685
prop_Container_addTwo cdata i1 i2 =
686
  fn i1 i2 cont == fn i2 i1 cont &&
687
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
688
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
689
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
690

    
691
prop_Container_nameOf :: Node.Node -> Property
692
prop_Container_nameOf node =
693
  let nl = makeSmallCluster node 1
694
      fnode = head (Container.elems nl)
695
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
696

    
697
-- | We test that in a cluster, given a random node, we can find it by
698
-- its name and alias, as long as all names and aliases are unique,
699
-- and that we fail to find a non-existing name.
700
prop_Container_findByName :: Property
701
prop_Container_findByName =
702
  forAll (genNode (Just 1) Nothing) $ \node ->
703
  forAll (choose (1, 20)) $ \ cnt ->
704
  forAll (choose (0, cnt - 1)) $ \ fidx ->
705
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
706
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
707
  let names = zip (take cnt allnames) (drop cnt allnames)
708
      nl = makeSmallCluster node cnt
709
      nodes = Container.elems nl
710
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
711
                                             nn { Node.name = name,
712
                                                  Node.alias = alias }))
713
               $ zip names nodes
714
      nl' = Container.fromList nodes'
715
      target = snd (nodes' !! fidx)
716
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
717
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
718
     printTestCase "Found non-existing name"
719
       (isNothing (Container.findByName nl' othername))
720

    
721
testSuite "Container"
722
            [ 'prop_Container_addTwo
723
            , 'prop_Container_nameOf
724
            , 'prop_Container_findByName
725
            ]
726

    
727
-- ** Instance tests
728

    
729
-- Simple instance tests, we only have setter/getters
730

    
731
prop_Instance_creat :: Instance.Instance -> Property
732
prop_Instance_creat inst =
733
  Instance.name inst ==? Instance.alias inst
734

    
735
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
736
prop_Instance_setIdx inst idx =
737
  Instance.idx (Instance.setIdx inst idx) ==? idx
738

    
739
prop_Instance_setName :: Instance.Instance -> String -> Bool
740
prop_Instance_setName inst name =
741
  Instance.name newinst == name &&
742
  Instance.alias newinst == name
743
    where newinst = Instance.setName inst name
744

    
745
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
746
prop_Instance_setAlias inst name =
747
  Instance.name newinst == Instance.name inst &&
748
  Instance.alias newinst == name
749
    where newinst = Instance.setAlias inst name
750

    
751
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
752
prop_Instance_setPri inst pdx =
753
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
754

    
755
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
756
prop_Instance_setSec inst sdx =
757
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
758

    
759
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
760
prop_Instance_setBoth inst pdx sdx =
761
  Instance.pNode si == pdx && Instance.sNode si == sdx
762
    where si = Instance.setBoth inst pdx sdx
763

    
764
prop_Instance_shrinkMG :: Instance.Instance -> Property
765
prop_Instance_shrinkMG inst =
766
  Instance.mem inst >= 2 * Types.unitMem ==>
767
    case Instance.shrinkByType inst Types.FailMem of
768
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
769
      _ -> False
770

    
771
prop_Instance_shrinkMF :: Instance.Instance -> Property
772
prop_Instance_shrinkMF inst =
773
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
774
    let inst' = inst { Instance.mem = mem}
775
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
776

    
777
prop_Instance_shrinkCG :: Instance.Instance -> Property
778
prop_Instance_shrinkCG inst =
779
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
780
    case Instance.shrinkByType inst Types.FailCPU of
781
      Types.Ok inst' ->
782
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
783
      _ -> False
784

    
785
prop_Instance_shrinkCF :: Instance.Instance -> Property
786
prop_Instance_shrinkCF inst =
787
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
788
    let inst' = inst { Instance.vcpus = vcpus }
789
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
790

    
791
prop_Instance_shrinkDG :: Instance.Instance -> Property
792
prop_Instance_shrinkDG inst =
793
  Instance.dsk inst >= 2 * Types.unitDsk ==>
794
    case Instance.shrinkByType inst Types.FailDisk of
795
      Types.Ok inst' ->
796
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
797
      _ -> False
798

    
799
prop_Instance_shrinkDF :: Instance.Instance -> Property
800
prop_Instance_shrinkDF inst =
801
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
802
    let inst' = inst { Instance.dsk = dsk }
803
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
804

    
805
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
806
prop_Instance_setMovable inst m =
807
  Instance.movable inst' ==? m
808
    where inst' = Instance.setMovable inst m
809

    
810
testSuite "Instance"
811
            [ 'prop_Instance_creat
812
            , 'prop_Instance_setIdx
813
            , 'prop_Instance_setName
814
            , 'prop_Instance_setAlias
815
            , 'prop_Instance_setPri
816
            , 'prop_Instance_setSec
817
            , 'prop_Instance_setBoth
818
            , 'prop_Instance_shrinkMG
819
            , 'prop_Instance_shrinkMF
820
            , 'prop_Instance_shrinkCG
821
            , 'prop_Instance_shrinkCF
822
            , 'prop_Instance_shrinkDG
823
            , 'prop_Instance_shrinkDF
824
            , 'prop_Instance_setMovable
825
            ]
826

    
827
-- ** Backends
828

    
829
-- *** Text backend tests
830

    
831
-- Instance text loader tests
832

    
833
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
834
                        -> NonEmptyList Char -> [Char]
835
                        -> NonNegative Int -> NonNegative Int -> Bool
836
                        -> Types.DiskTemplate -> Int -> Property
837
prop_Text_Load_Instance name mem dsk vcpus status
838
                        (NonEmpty pnode) snode
839
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
840
  pnode /= snode && pdx /= sdx ==>
841
  let vcpus_s = show vcpus
842
      dsk_s = show dsk
843
      mem_s = show mem
844
      su_s = show su
845
      status_s = Types.instanceStatusToRaw status
846
      ndx = if null snode
847
              then [(pnode, pdx)]
848
              else [(pnode, pdx), (snode, sdx)]
849
      nl = Data.Map.fromList ndx
850
      tags = ""
851
      sbal = if autobal then "Y" else "N"
852
      sdt = Types.diskTemplateToRaw dt
853
      inst = Text.loadInst nl
854
             [name, mem_s, dsk_s, vcpus_s, status_s,
855
              sbal, pnode, snode, sdt, tags, su_s]
856
      fail1 = Text.loadInst nl
857
              [name, mem_s, dsk_s, vcpus_s, status_s,
858
               sbal, pnode, pnode, tags]
859
  in case inst of
860
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
861
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
862
                                        \ loading the instance" $
863
               Instance.name i == name &&
864
               Instance.vcpus i == vcpus &&
865
               Instance.mem i == mem &&
866
               Instance.pNode i == pdx &&
867
               Instance.sNode i == (if null snode
868
                                      then Node.noSecondary
869
                                      else sdx) &&
870
               Instance.autoBalance i == autobal &&
871
               Instance.spindleUse i == su &&
872
               Types.isBad fail1
873

    
874
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
875
prop_Text_Load_InstanceFail ktn fields =
876
  length fields /= 10 && length fields /= 11 ==>
877
    case Text.loadInst nl fields of
878
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
879
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
880
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
881
    where nl = Data.Map.fromList ktn
882

    
883
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
884
                    -> Int -> Bool -> Bool
885
prop_Text_Load_Node name tm nm fm td fd tc fo =
886
  let conv v = if v < 0
887
                 then "?"
888
                 else show v
889
      tm_s = conv tm
890
      nm_s = conv nm
891
      fm_s = conv fm
892
      td_s = conv td
893
      fd_s = conv fd
894
      tc_s = conv tc
895
      fo_s = if fo
896
               then "Y"
897
               else "N"
898
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
899
      gid = Group.uuid defGroup
900
  in case Text.loadNode defGroupAssoc
901
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
902
       Nothing -> False
903
       Just (name', node) ->
904
         if fo || any_broken
905
           then Node.offline node
906
           else Node.name node == name' && name' == name &&
907
                Node.alias node == name &&
908
                Node.tMem node == fromIntegral tm &&
909
                Node.nMem node == nm &&
910
                Node.fMem node == fm &&
911
                Node.tDsk node == fromIntegral td &&
912
                Node.fDsk node == fd &&
913
                Node.tCpu node == fromIntegral tc
914

    
915
prop_Text_Load_NodeFail :: [String] -> Property
916
prop_Text_Load_NodeFail fields =
917
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
918

    
919
prop_Text_NodeLSIdempotent :: Property
920
prop_Text_NodeLSIdempotent =
921
  forAll (genNode (Just 1) Nothing) $ \node ->
922
  -- override failN1 to what loadNode returns by default
923
  let n = Node.setPolicy Types.defIPolicy $
924
          node { Node.failN1 = True, Node.offline = False }
925
  in
926
    (Text.loadNode defGroupAssoc.
927
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
928
    Just (Node.name n, n)
929

    
930
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
931
prop_Text_ISpecIdempotent ispec =
932
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
933
       Text.serializeISpec $ ispec of
934
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
935
    Types.Ok ispec' -> ispec ==? ispec'
936

    
937
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
938
prop_Text_IPolicyIdempotent ipol =
939
  case Text.loadIPolicy . Utils.sepSplit '|' $
940
       Text.serializeIPolicy owner ipol of
941
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
942
    Types.Ok res -> (owner, ipol) ==? res
943
  where owner = "dummy"
944

    
945
-- | This property, while being in the text tests, does more than just
946
-- test end-to-end the serialisation and loading back workflow; it
947
-- also tests the Loader.mergeData and the actuall
948
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
949
-- allocations, not for the business logic). As such, it's a quite
950
-- complex and slow test, and that's the reason we restrict it to
951
-- small cluster sizes.
952
prop_Text_CreateSerialise :: Property
953
prop_Text_CreateSerialise =
954
  forAll genTags $ \ctags ->
955
  forAll (choose (1, 20)) $ \maxiter ->
956
  forAll (choose (2, 10)) $ \count ->
957
  forAll genOnlineNode $ \node ->
958
  forAll (genInstanceSmallerThanNode node) $ \inst ->
959
  let nl = makeSmallCluster node count
960
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
961
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
962
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
963
     of
964
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
965
       Types.Ok (_, _, _, [], _) -> printTestCase
966
                                    "Failed to allocate: no allocations" False
967
       Types.Ok (_, nl', il', _, _) ->
968
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
969
                     Types.defIPolicy
970
             saved = Text.serializeCluster cdata
971
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
972
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
973
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
974
                ctags ==? ctags2 .&&.
975
                Types.defIPolicy ==? cpol2 .&&.
976
                il' ==? il2 .&&.
977
                defGroupList ==? gl2 .&&.
978
                nl' ==? nl2
979

    
980
testSuite "Text"
981
            [ 'prop_Text_Load_Instance
982
            , 'prop_Text_Load_InstanceFail
983
            , 'prop_Text_Load_Node
984
            , 'prop_Text_Load_NodeFail
985
            , 'prop_Text_NodeLSIdempotent
986
            , 'prop_Text_ISpecIdempotent
987
            , 'prop_Text_IPolicyIdempotent
988
            , 'prop_Text_CreateSerialise
989
            ]
990

    
991
-- *** Simu backend
992

    
993
-- | Generates a tuple of specs for simulation.
994
genSimuSpec :: Gen (String, Int, Int, Int, Int)
995
genSimuSpec = do
996
  pol <- elements [C.allocPolicyPreferred,
997
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
998
                  "p", "a", "u"]
999
 -- should be reasonable (nodes/group), bigger values only complicate
1000
 -- the display of failed tests, and we don't care (in this particular
1001
 -- test) about big node groups
1002
  nodes <- choose (0, 20)
1003
  dsk <- choose (0, maxDsk)
1004
  mem <- choose (0, maxMem)
1005
  cpu <- choose (0, maxCpu)
1006
  return (pol, nodes, dsk, mem, cpu)
1007

    
1008
-- | Checks that given a set of corrects specs, we can load them
1009
-- successfully, and that at high-level the values look right.
1010
prop_SimuLoad :: Property
1011
prop_SimuLoad =
1012
  forAll (choose (0, 10)) $ \ngroups ->
1013
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
1014
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
1015
                                          p n d m c::String) specs
1016
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
1017
      mdc_in = concatMap (\(_, n, d, m, c) ->
1018
                            replicate n (fromIntegral m, fromIntegral d,
1019
                                         fromIntegral c,
1020
                                         fromIntegral m, fromIntegral d))
1021
               specs :: [(Double, Double, Double, Int, Int)]
1022
  in case Simu.parseData strspecs of
1023
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1024
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1025
         let nodes = map snd $ IntMap.toAscList nl
1026
             nidx = map Node.idx nodes
1027
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1028
                                   Node.fMem n, Node.fDsk n)) nodes
1029
         in
1030
         Container.size gl ==? ngroups .&&.
1031
         Container.size nl ==? totnodes .&&.
1032
         Container.size il ==? 0 .&&.
1033
         length tags ==? 0 .&&.
1034
         ipol ==? Types.defIPolicy .&&.
1035
         nidx ==? [1..totnodes] .&&.
1036
         mdc_in ==? mdc_out .&&.
1037
         map Group.iPolicy (Container.elems gl) ==?
1038
             replicate ngroups Types.defIPolicy
1039

    
1040
testSuite "Simu"
1041
            [ 'prop_SimuLoad
1042
            ]
1043

    
1044
-- ** Node tests
1045

    
1046
prop_Node_setAlias :: Node.Node -> String -> Bool
1047
prop_Node_setAlias node name =
1048
  Node.name newnode == Node.name node &&
1049
  Node.alias newnode == name
1050
    where newnode = Node.setAlias node name
1051

    
1052
prop_Node_setOffline :: Node.Node -> Bool -> Property
1053
prop_Node_setOffline node status =
1054
  Node.offline newnode ==? status
1055
    where newnode = Node.setOffline node status
1056

    
1057
prop_Node_setXmem :: Node.Node -> Int -> Property
1058
prop_Node_setXmem node xm =
1059
  Node.xMem newnode ==? xm
1060
    where newnode = Node.setXmem node xm
1061

    
1062
prop_Node_setMcpu :: Node.Node -> Double -> Property
1063
prop_Node_setMcpu node mc =
1064
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1065
    where newnode = Node.setMcpu node mc
1066

    
1067
-- | Check that an instance add with too high memory or disk will be
1068
-- rejected.
1069
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1070
prop_Node_addPriFM node inst =
1071
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1072
  not (Instance.isOffline inst) ==>
1073
  case Node.addPri node inst'' of
1074
    Types.OpFail Types.FailMem -> True
1075
    _ -> False
1076
  where inst' = setInstanceSmallerThanNode node inst
1077
        inst'' = inst' { Instance.mem = Instance.mem inst }
1078

    
1079
-- | Check that adding a primary instance with too much disk fails
1080
-- with type FailDisk.
1081
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1082
prop_Node_addPriFD node inst =
1083
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1084
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1085
  let inst' = setInstanceSmallerThanNode node inst
1086
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1087
                     , Instance.diskTemplate = dt }
1088
  in case Node.addPri node inst'' of
1089
       Types.OpFail Types.FailDisk -> True
1090
       _ -> False
1091

    
1092
-- | Check that adding a primary instance with too many VCPUs fails
1093
-- with type FailCPU.
1094
prop_Node_addPriFC :: Property
1095
prop_Node_addPriFC =
1096
  forAll (choose (1, maxCpu)) $ \extra ->
1097
  forAll genOnlineNode $ \node ->
1098
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1099
  let inst' = setInstanceSmallerThanNode node inst
1100
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1101
  in case Node.addPri node inst'' of
1102
       Types.OpFail Types.FailCPU -> property True
1103
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1104

    
1105
-- | Check that an instance add with too high memory or disk will be
1106
-- rejected.
1107
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1108
prop_Node_addSec node inst pdx =
1109
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1110
    not (Instance.isOffline inst)) ||
1111
   Instance.dsk inst >= Node.fDsk node) &&
1112
  not (Node.failN1 node) ==>
1113
      isFailure (Node.addSec node inst pdx)
1114

    
1115
-- | Check that an offline instance with reasonable disk size but
1116
-- extra mem/cpu can always be added.
1117
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1118
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1119
  forAll genOnlineNode $ \node ->
1120
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1121
  let inst' = inst { Instance.runSt = Types.AdminOffline
1122
                   , Instance.mem = Node.availMem node + extra_mem
1123
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1124
  in case Node.addPri node inst' of
1125
       Types.OpGood _ -> property True
1126
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1127

    
1128
-- | Check that an offline instance with reasonable disk size but
1129
-- extra mem/cpu can always be added.
1130
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1131
                        -> Types.Ndx -> Property
1132
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1133
  forAll genOnlineNode $ \node ->
1134
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1135
  let inst' = inst { Instance.runSt = Types.AdminOffline
1136
                   , Instance.mem = Node.availMem node + extra_mem
1137
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1138
                   , Instance.diskTemplate = Types.DTDrbd8 }
1139
  in case Node.addSec node inst' pdx of
1140
       Types.OpGood _ -> property True
1141
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1142

    
1143
-- | Checks for memory reservation changes.
1144
prop_Node_rMem :: Instance.Instance -> Property
1145
prop_Node_rMem inst =
1146
  not (Instance.isOffline inst) ==>
1147
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1148
  -- ab = auto_balance, nb = non-auto_balance
1149
  -- we use -1 as the primary node of the instance
1150
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1151
                   , Instance.diskTemplate = Types.DTDrbd8 }
1152
      inst_ab = setInstanceSmallerThanNode node inst'
1153
      inst_nb = inst_ab { Instance.autoBalance = False }
1154
      -- now we have the two instances, identical except the
1155
      -- autoBalance attribute
1156
      orig_rmem = Node.rMem node
1157
      inst_idx = Instance.idx inst_ab
1158
      node_add_ab = Node.addSec node inst_ab (-1)
1159
      node_add_nb = Node.addSec node inst_nb (-1)
1160
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1161
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1162
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1163
       (Types.OpGood a_ab, Types.OpGood a_nb,
1164
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1165
         printTestCase "Consistency checks failed" $
1166
           Node.rMem a_ab >  orig_rmem &&
1167
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1168
           Node.rMem a_nb == orig_rmem &&
1169
           Node.rMem d_ab == orig_rmem &&
1170
           Node.rMem d_nb == orig_rmem &&
1171
           -- this is not related to rMem, but as good a place to
1172
           -- test as any
1173
           inst_idx `elem` Node.sList a_ab &&
1174
           inst_idx `notElem` Node.sList d_ab
1175
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1176

    
1177
-- | Check mdsk setting.
1178
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1179
prop_Node_setMdsk node mx =
1180
  Node.loDsk node' >= 0 &&
1181
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1182
  Node.availDisk node' >= 0 &&
1183
  Node.availDisk node' <= Node.fDsk node' &&
1184
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1185
  Node.mDsk node' == mx'
1186
    where node' = Node.setMdsk node mx'
1187
          SmallRatio mx' = mx
1188

    
1189
-- Check tag maps
1190
prop_Node_tagMaps_idempotent :: Property
1191
prop_Node_tagMaps_idempotent =
1192
  forAll genTags $ \tags ->
1193
  Node.delTags (Node.addTags m tags) tags ==? m
1194
    where m = Data.Map.empty
1195

    
1196
prop_Node_tagMaps_reject :: Property
1197
prop_Node_tagMaps_reject =
1198
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1199
  let m = Node.addTags Data.Map.empty tags
1200
  in all (\t -> Node.rejectAddTags m [t]) tags
1201

    
1202
prop_Node_showField :: Node.Node -> Property
1203
prop_Node_showField node =
1204
  forAll (elements Node.defaultFields) $ \ field ->
1205
  fst (Node.showHeader field) /= Types.unknownField &&
1206
  Node.showField node field /= Types.unknownField
1207

    
1208
prop_Node_computeGroups :: [Node.Node] -> Bool
1209
prop_Node_computeGroups nodes =
1210
  let ng = Node.computeGroups nodes
1211
      onlyuuid = map fst ng
1212
  in length nodes == sum (map (length . snd) ng) &&
1213
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1214
     length (nub onlyuuid) == length onlyuuid &&
1215
     (null nodes || not (null ng))
1216

    
1217
-- Check idempotence of add/remove operations
1218
prop_Node_addPri_idempotent :: Property
1219
prop_Node_addPri_idempotent =
1220
  forAll genOnlineNode $ \node ->
1221
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1222
  case Node.addPri node inst of
1223
    Types.OpGood node' -> Node.removePri node' inst ==? node
1224
    _ -> failTest "Can't add instance"
1225

    
1226
prop_Node_addSec_idempotent :: Property
1227
prop_Node_addSec_idempotent =
1228
  forAll genOnlineNode $ \node ->
1229
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1230
  let pdx = Node.idx node + 1
1231
      inst' = Instance.setPri inst pdx
1232
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1233
  in case Node.addSec node inst'' pdx of
1234
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1235
       _ -> failTest "Can't add instance"
1236

    
1237
testSuite "Node"
1238
            [ 'prop_Node_setAlias
1239
            , 'prop_Node_setOffline
1240
            , 'prop_Node_setMcpu
1241
            , 'prop_Node_setXmem
1242
            , 'prop_Node_addPriFM
1243
            , 'prop_Node_addPriFD
1244
            , 'prop_Node_addPriFC
1245
            , 'prop_Node_addSec
1246
            , 'prop_Node_addOfflinePri
1247
            , 'prop_Node_addOfflineSec
1248
            , 'prop_Node_rMem
1249
            , 'prop_Node_setMdsk
1250
            , 'prop_Node_tagMaps_idempotent
1251
            , 'prop_Node_tagMaps_reject
1252
            , 'prop_Node_showField
1253
            , 'prop_Node_computeGroups
1254
            , 'prop_Node_addPri_idempotent
1255
            , 'prop_Node_addSec_idempotent
1256
            ]
1257

    
1258
-- ** Cluster tests
1259

    
1260
-- | Check that the cluster score is close to zero for a homogeneous
1261
-- cluster.
1262
prop_Score_Zero :: Node.Node -> Property
1263
prop_Score_Zero node =
1264
  forAll (choose (1, 1024)) $ \count ->
1265
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1266
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1267
  let fn = Node.buildPeers node Container.empty
1268
      nlst = replicate count fn
1269
      score = Cluster.compCVNodes nlst
1270
  -- we can't say == 0 here as the floating point errors accumulate;
1271
  -- this should be much lower than the default score in CLI.hs
1272
  in score <= 1e-12
1273

    
1274
-- | Check that cluster stats are sane.
1275
prop_CStats_sane :: Property
1276
prop_CStats_sane =
1277
  forAll (choose (1, 1024)) $ \count ->
1278
  forAll genOnlineNode $ \node ->
1279
  let fn = Node.buildPeers node Container.empty
1280
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1281
      nl = Container.fromList nlst
1282
      cstats = Cluster.totalResources nl
1283
  in Cluster.csAdsk cstats >= 0 &&
1284
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1285

    
1286
-- | Check that one instance is allocated correctly, without
1287
-- rebalances needed.
1288
prop_ClusterAlloc_sane :: Instance.Instance -> Property
1289
prop_ClusterAlloc_sane inst =
1290
  forAll (choose (5, 20)) $ \count ->
1291
  forAll genOnlineNode $ \node ->
1292
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1293
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1294
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1295
     Cluster.tryAlloc nl il inst' of
1296
       Types.Bad _ -> False
1297
       Types.Ok as ->
1298
         case Cluster.asSolution as of
1299
           Nothing -> False
1300
           Just (xnl, xi, _, cv) ->
1301
             let il' = Container.add (Instance.idx xi) xi il
1302
                 tbl = Cluster.Table xnl il' cv []
1303
             in not (canBalance tbl True True False)
1304

    
1305
-- | Checks that on a 2-5 node cluster, we can allocate a random
1306
-- instance spec via tiered allocation (whatever the original instance
1307
-- spec), on either one or two nodes. Furthermore, we test that
1308
-- computed allocation statistics are correct.
1309
prop_ClusterCanTieredAlloc :: Instance.Instance -> Property
1310
prop_ClusterCanTieredAlloc inst =
1311
  forAll (choose (2, 5)) $ \count ->
1312
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1313
  let nl = makeSmallCluster node count
1314
      il = Container.empty
1315
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1316
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1317
  in case allocnodes >>= \allocnodes' ->
1318
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1319
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1320
       Types.Ok (_, nl', il', ixes, cstats) ->
1321
         let (ai_alloc, ai_pool, ai_unav) =
1322
               Cluster.computeAllocationDelta
1323
                (Cluster.totalResources nl)
1324
                (Cluster.totalResources nl')
1325
             all_nodes = Container.elems nl
1326
         in property (not (null ixes)) .&&.
1327
            IntMap.size il' ==? length ixes .&&.
1328
            length ixes ==? length cstats .&&.
1329
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1330
              sum (map Node.hiCpu all_nodes) .&&.
1331
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1332
              sum (map Node.tCpu all_nodes) .&&.
1333
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1334
              truncate (sum (map Node.tMem all_nodes)) .&&.
1335
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1336
              truncate (sum (map Node.tDsk all_nodes))
1337

    
1338
-- | Helper function to create a cluster with the given range of nodes
1339
-- and allocate an instance on it.
1340
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1341
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1342
genClusterAlloc count node inst =
1343
  let nl = makeSmallCluster node count
1344
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1345
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1346
     Cluster.tryAlloc nl Container.empty inst of
1347
       Types.Bad _ -> Types.Bad "Can't allocate"
1348
       Types.Ok as ->
1349
         case Cluster.asSolution as of
1350
           Nothing -> Types.Bad "Empty solution?"
1351
           Just (xnl, xi, _, _) ->
1352
             let xil = Container.add (Instance.idx xi) xi Container.empty
1353
             in Types.Ok (xnl, xil, xi)
1354

    
1355
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1356
-- we can also relocate it.
1357
prop_ClusterAllocRelocate :: Property
1358
prop_ClusterAllocRelocate =
1359
  forAll (choose (4, 8)) $ \count ->
1360
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1361
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1362
  case genClusterAlloc count node inst of
1363
    Types.Bad msg -> failTest msg
1364
    Types.Ok (nl, il, inst') ->
1365
      case IAlloc.processRelocate defGroupList nl il
1366
             (Instance.idx inst) 1
1367
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1368
                 then Instance.sNode
1369
                 else Instance.pNode) inst'] of
1370
        Types.Ok _ -> property True
1371
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1372

    
1373
-- | Helper property checker for the result of a nodeEvac or
1374
-- changeGroup operation.
1375
check_EvacMode :: Group.Group -> Instance.Instance
1376
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1377
               -> Property
1378
check_EvacMode grp inst result =
1379
  case result of
1380
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1381
    Types.Ok (_, _, es) ->
1382
      let moved = Cluster.esMoved es
1383
          failed = Cluster.esFailed es
1384
          opcodes = not . null $ Cluster.esOpCodes es
1385
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1386
         failmsg "'opcodes' is null" opcodes .&&.
1387
         case moved of
1388
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1389
                               .&&.
1390
                               failmsg "wrong target group"
1391
                                         (gdx == Group.idx grp)
1392
           v -> failmsg  ("invalid solution: " ++ show v) False
1393
  where failmsg :: String -> Bool -> Property
1394
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1395
        idx = Instance.idx inst
1396

    
1397
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1398
-- we can also node-evacuate it.
1399
prop_ClusterAllocEvacuate :: Property
1400
prop_ClusterAllocEvacuate =
1401
  forAll (choose (4, 8)) $ \count ->
1402
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1403
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1404
  case genClusterAlloc count node inst of
1405
    Types.Bad msg -> failTest msg
1406
    Types.Ok (nl, il, inst') ->
1407
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1408
                              Cluster.tryNodeEvac defGroupList nl il mode
1409
                                [Instance.idx inst']) .
1410
                              evacModeOptions .
1411
                              Instance.mirrorType $ inst'
1412

    
1413
-- | Checks that on a 4-8 node cluster with two node groups, once we
1414
-- allocate an instance on the first node group, we can also change
1415
-- its group.
1416
prop_ClusterAllocChangeGroup :: Property
1417
prop_ClusterAllocChangeGroup =
1418
  forAll (choose (4, 8)) $ \count ->
1419
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1420
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1421
  case genClusterAlloc count node inst of
1422
    Types.Bad msg -> failTest msg
1423
    Types.Ok (nl, il, inst') ->
1424
      -- we need to add a second node group and nodes to the cluster
1425
      let nl2 = Container.elems $ makeSmallCluster node count
1426
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1427
          maxndx = maximum . map Node.idx $ nl2
1428
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1429
                             , Node.idx = Node.idx n + maxndx }) nl2
1430
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1431
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1432
          nl' = IntMap.union nl nl4
1433
      in check_EvacMode grp2 inst' $
1434
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1435

    
1436
-- | Check that allocating multiple instances on a cluster, then
1437
-- adding an empty node, results in a valid rebalance.
1438
prop_ClusterAllocBalance :: Property
1439
prop_ClusterAllocBalance =
1440
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1441
  forAll (choose (3, 5)) $ \count ->
1442
  not (Node.offline node) && not (Node.failN1 node) ==>
1443
  let nl = makeSmallCluster node count
1444
      (hnode, nl') = IntMap.deleteFindMax nl
1445
      il = Container.empty
1446
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1447
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1448
  in case allocnodes >>= \allocnodes' ->
1449
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1450
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1451
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1452
       Types.Ok (_, xnl, il', _, _) ->
1453
         let ynl = Container.add (Node.idx hnode) hnode xnl
1454
             cv = Cluster.compCV ynl
1455
             tbl = Cluster.Table ynl il' cv []
1456
         in printTestCase "Failed to rebalance" $
1457
            canBalance tbl True True False
1458

    
1459
-- | Checks consistency.
1460
prop_ClusterCheckConsistency :: Node.Node -> Instance.Instance -> Bool
1461
prop_ClusterCheckConsistency node inst =
1462
  let nl = makeSmallCluster node 3
1463
      [node1, node2, node3] = Container.elems nl
1464
      node3' = node3 { Node.group = 1 }
1465
      nl' = Container.add (Node.idx node3') node3' nl
1466
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1467
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1468
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1469
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1470
  in null (ccheck [(0, inst1)]) &&
1471
     null (ccheck [(0, inst2)]) &&
1472
     (not . null $ ccheck [(0, inst3)])
1473

    
1474
-- | For now, we only test that we don't lose instances during the split.
1475
prop_ClusterSplitCluster :: Node.Node -> Instance.Instance -> Property
1476
prop_ClusterSplitCluster node inst =
1477
  forAll (choose (0, 100)) $ \icnt ->
1478
  let nl = makeSmallCluster node 2
1479
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1480
                   (nl, Container.empty) [1..icnt]
1481
      gni = Cluster.splitCluster nl' il'
1482
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1483
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1484
                                 (Container.elems nl'')) gni
1485

    
1486
-- | Helper function to check if we can allocate an instance on a
1487
-- given node list.
1488
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1489
canAllocOn nl reqnodes inst =
1490
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1491
       Cluster.tryAlloc nl (Container.empty) inst of
1492
       Types.Bad _ -> False
1493
       Types.Ok as ->
1494
         case Cluster.asSolution as of
1495
           Nothing -> False
1496
           Just _ -> True
1497

    
1498
-- | Checks that allocation obeys minimum and maximum instance
1499
-- policies. The unittest generates a random node, duplicates it /count/
1500
-- times, and generates a random instance that can be allocated on
1501
-- this mini-cluster; it then checks that after applying a policy that
1502
-- the instance doesn't fits, the allocation fails.
1503
prop_ClusterAllocPolicy :: Node.Node -> Property
1504
prop_ClusterAllocPolicy node =
1505
  -- rqn is the required nodes (1 or 2)
1506
  forAll (choose (1, 2)) $ \rqn ->
1507
  forAll (choose (5, 20)) $ \count ->
1508
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1509
         $ \inst ->
1510
  forAll (arbitrary `suchThat` (isFailure .
1511
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1512
  let node' = Node.setPolicy ipol node
1513
      nl = makeSmallCluster node' count
1514
  in not $ canAllocOn nl rqn inst
1515

    
1516
testSuite "Cluster"
1517
            [ 'prop_Score_Zero
1518
            , 'prop_CStats_sane
1519
            , 'prop_ClusterAlloc_sane
1520
            , 'prop_ClusterCanTieredAlloc
1521
            , 'prop_ClusterAllocRelocate
1522
            , 'prop_ClusterAllocEvacuate
1523
            , 'prop_ClusterAllocChangeGroup
1524
            , 'prop_ClusterAllocBalance
1525
            , 'prop_ClusterCheckConsistency
1526
            , 'prop_ClusterSplitCluster
1527
            , 'prop_ClusterAllocPolicy
1528
            ]
1529

    
1530
-- ** OpCodes tests
1531

    
1532
-- | Check that opcode serialization is idempotent.
1533
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1534
prop_OpCodes_serialization op =
1535
  case J.readJSON (J.showJSON op) of
1536
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1537
    J.Ok op' -> op ==? op'
1538

    
1539
testSuite "OpCodes"
1540
            [ 'prop_OpCodes_serialization ]
1541

    
1542
-- ** Jobs tests
1543

    
1544
-- | Check that (queued) job\/opcode status serialization is idempotent.
1545
prop_OpStatus_serialization :: Jobs.OpStatus -> Property
1546
prop_OpStatus_serialization os =
1547
  case J.readJSON (J.showJSON os) of
1548
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1549
    J.Ok os' -> os ==? os'
1550

    
1551
prop_JobStatus_serialization :: Jobs.JobStatus -> Property
1552
prop_JobStatus_serialization js =
1553
  case J.readJSON (J.showJSON js) of
1554
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1555
    J.Ok js' -> js ==? js'
1556

    
1557
testSuite "Jobs"
1558
            [ 'prop_OpStatus_serialization
1559
            , 'prop_JobStatus_serialization
1560
            ]
1561

    
1562
-- ** Loader tests
1563

    
1564
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1565
prop_Loader_lookupNode ktn inst node =
1566
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1567
    where nl = Data.Map.fromList ktn
1568

    
1569
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1570
prop_Loader_lookupInstance kti inst =
1571
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1572
    where il = Data.Map.fromList kti
1573

    
1574
prop_Loader_assignIndices :: Property
1575
prop_Loader_assignIndices =
1576
  -- generate nodes with unique names
1577
  forAll (arbitrary `suchThat`
1578
          (\nodes ->
1579
             let names = map Node.name nodes
1580
             in length names == length (nub names))) $ \nodes ->
1581
  let (nassoc, kt) =
1582
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1583
  in Data.Map.size nassoc == length nodes &&
1584
     Container.size kt == length nodes &&
1585
     if not (null nodes)
1586
       then maximum (IntMap.keys kt) == length nodes - 1
1587
       else True
1588

    
1589
-- | Checks that the number of primary instances recorded on the nodes
1590
-- is zero.
1591
prop_Loader_mergeData :: [Node.Node] -> Bool
1592
prop_Loader_mergeData ns =
1593
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1594
  in case Loader.mergeData [] [] [] []
1595
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1596
    Types.Bad _ -> False
1597
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1598
      let nodes = Container.elems nl
1599
          instances = Container.elems il
1600
      in (sum . map (length . Node.pList)) nodes == 0 &&
1601
         null instances
1602

    
1603
-- | Check that compareNameComponent on equal strings works.
1604
prop_Loader_compareNameComponent_equal :: String -> Bool
1605
prop_Loader_compareNameComponent_equal s =
1606
  BasicTypes.compareNameComponent s s ==
1607
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1608

    
1609
-- | Check that compareNameComponent on prefix strings works.
1610
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1611
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1612
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1613
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1614

    
1615
testSuite "Loader"
1616
            [ 'prop_Loader_lookupNode
1617
            , 'prop_Loader_lookupInstance
1618
            , 'prop_Loader_assignIndices
1619
            , 'prop_Loader_mergeData
1620
            , 'prop_Loader_compareNameComponent_equal
1621
            , 'prop_Loader_compareNameComponent_prefix
1622
            ]
1623

    
1624
-- ** Types tests
1625

    
1626
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1627
prop_Types_AllocPolicy_serialisation apol =
1628
  case J.readJSON (J.showJSON apol) of
1629
    J.Ok p -> p ==? apol
1630
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1631

    
1632
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1633
prop_Types_DiskTemplate_serialisation dt =
1634
  case J.readJSON (J.showJSON dt) of
1635
    J.Ok p -> p ==? dt
1636
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1637

    
1638
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1639
prop_Types_ISpec_serialisation ispec =
1640
  case J.readJSON (J.showJSON ispec) of
1641
    J.Ok p -> p ==? ispec
1642
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1643

    
1644
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1645
prop_Types_IPolicy_serialisation ipol =
1646
  case J.readJSON (J.showJSON ipol) of
1647
    J.Ok p -> p ==? ipol
1648
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1649

    
1650
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1651
prop_Types_EvacMode_serialisation em =
1652
  case J.readJSON (J.showJSON em) of
1653
    J.Ok p -> p ==? em
1654
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1655

    
1656
prop_Types_opToResult :: Types.OpResult Int -> Bool
1657
prop_Types_opToResult op =
1658
  case op of
1659
    Types.OpFail _ -> Types.isBad r
1660
    Types.OpGood v -> case r of
1661
                        Types.Bad _ -> False
1662
                        Types.Ok v' -> v == v'
1663
  where r = Types.opToResult op
1664

    
1665
prop_Types_eitherToResult :: Either String Int -> Bool
1666
prop_Types_eitherToResult ei =
1667
  case ei of
1668
    Left _ -> Types.isBad r
1669
    Right v -> case r of
1670
                 Types.Bad _ -> False
1671
                 Types.Ok v' -> v == v'
1672
    where r = Types.eitherToResult ei
1673

    
1674
testSuite "Types"
1675
            [ 'prop_Types_AllocPolicy_serialisation
1676
            , 'prop_Types_DiskTemplate_serialisation
1677
            , 'prop_Types_ISpec_serialisation
1678
            , 'prop_Types_IPolicy_serialisation
1679
            , 'prop_Types_EvacMode_serialisation
1680
            , 'prop_Types_opToResult
1681
            , 'prop_Types_eitherToResult
1682
            ]
1683

    
1684
-- ** CLI tests
1685

    
1686
-- | Test correct parsing.
1687
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1688
prop_CLI_parseISpec descr dsk mem cpu =
1689
  let str = printf "%d,%d,%d" dsk mem cpu::String
1690
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1691

    
1692
-- | Test parsing failure due to wrong section count.
1693
prop_CLI_parseISpecFail :: String -> Property
1694
prop_CLI_parseISpecFail descr =
1695
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1696
  forAll (replicateM nelems arbitrary) $ \values ->
1697
  let str = intercalate "," $ map show (values::[Int])
1698
  in case CLI.parseISpecString descr str of
1699
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1700
       _ -> property True
1701

    
1702
-- | Test parseYesNo.
1703
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1704
prop_CLI_parseYesNo def testval val =
1705
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1706
  if testval
1707
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1708
    else let result = CLI.parseYesNo def (Just actual_val)
1709
         in if actual_val `elem` ["yes", "no"]
1710
              then result ==? Types.Ok (actual_val == "yes")
1711
              else property $ Types.isBad result
1712

    
1713
-- | Helper to check for correct parsing of string arg.
1714
checkStringArg :: [Char]
1715
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1716
                   CLI.Options -> Maybe [Char])
1717
               -> Property
1718
checkStringArg val (opt, fn) =
1719
  let GetOpt.Option _ longs _ _ = opt
1720
  in case longs of
1721
       [] -> failTest "no long options?"
1722
       cmdarg:_ ->
1723
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1724
           Left e -> failTest $ "Failed to parse option: " ++ show e
1725
           Right (options, _) -> fn options ==? Just val
1726

    
1727
-- | Test a few string arguments.
1728
prop_CLI_StringArg :: [Char] -> Property
1729
prop_CLI_StringArg argument =
1730
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1731
             , (CLI.oDynuFile,      CLI.optDynuFile)
1732
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1733
             , (CLI.oReplay,        CLI.optReplay)
1734
             , (CLI.oPrintCommands, CLI.optShowCmds)
1735
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1736
             ]
1737
  in conjoin $ map (checkStringArg argument) args
1738

    
1739
-- | Helper to test that a given option is accepted OK with quick exit.
1740
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1741
checkEarlyExit name options param =
1742
  case CLI.parseOptsInner [param] name options of
1743
    Left (code, _) -> if code == 0
1744
                          then property True
1745
                          else failTest $ "Program " ++ name ++
1746
                                 " returns invalid code " ++ show code ++
1747
                                 " for option " ++ param
1748
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1749
         param ++ " as early exit one"
1750

    
1751
-- | Test that all binaries support some common options. There is
1752
-- nothing actually random about this test...
1753
prop_CLI_stdopts :: Property
1754
prop_CLI_stdopts =
1755
  let params = ["-h", "--help", "-V", "--version"]
1756
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1757
      -- apply checkEarlyExit across the cartesian product of params and opts
1758
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1759

    
1760
testSuite "CLI"
1761
          [ 'prop_CLI_parseISpec
1762
          , 'prop_CLI_parseISpecFail
1763
          , 'prop_CLI_parseYesNo
1764
          , 'prop_CLI_StringArg
1765
          , 'prop_CLI_stdopts
1766
          ]
1767

    
1768
-- * JSON tests
1769

    
1770
prop_JSON_toArray :: [Int] -> Property
1771
prop_JSON_toArray intarr =
1772
  let arr = map J.showJSON intarr in
1773
  case JSON.toArray (J.JSArray arr) of
1774
    Types.Ok arr' -> arr ==? arr'
1775
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1776

    
1777
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1778
prop_JSON_toArrayFail i s b =
1779
  -- poor man's instance Arbitrary JSValue
1780
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1781
  case JSON.toArray item of
1782
    Types.Bad _ -> property True
1783
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1784

    
1785
testSuite "JSON"
1786
          [ 'prop_JSON_toArray
1787
          , 'prop_JSON_toArrayFail
1788
          ]
1789

    
1790
-- * Luxi tests
1791

    
1792
instance Arbitrary Luxi.LuxiReq where
1793
  arbitrary = elements [minBound..maxBound]
1794

    
1795
instance Arbitrary Luxi.QrViaLuxi where
1796
  arbitrary = elements [minBound..maxBound]
1797

    
1798
instance Arbitrary Luxi.LuxiOp where
1799
  arbitrary = do
1800
    lreq <- arbitrary
1801
    case lreq of
1802
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> arbitrary
1803
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1804
                            getFields <*> arbitrary
1805
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1806
                             arbitrary <*> arbitrary
1807
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1808
                                getFields <*> arbitrary
1809
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1810
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1811
                              (listOf getFQDN) <*> arbitrary
1812
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1813
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1814
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> getName <*> getFQDN
1815
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1816
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1817
                                (resize maxOpCodes arbitrary)
1818
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1819
                                  getFields <*> pure J.JSNull <*>
1820
                                  pure J.JSNull <*> arbitrary
1821
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1822
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1823
                                 arbitrary
1824
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1825
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1826
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1827

    
1828
-- | Simple check that encoding/decoding of LuxiOp works.
1829
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1830
prop_Luxi_CallEncoding op =
1831
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1832

    
1833
-- | Helper to a get a temporary file name.
1834
getTempFileName :: IO FilePath
1835
getTempFileName = do
1836
  tempdir <- getTemporaryDirectory
1837
  (fpath, handle) <- openTempFile tempdir "luxitest"
1838
  _ <- hClose handle
1839
  removeFile fpath
1840
  return fpath
1841

    
1842
-- | Helper to execute recvMsg but return Nothing if we reach EOF.
1843
handleEOF :: (IO a) -> IO (Maybe a)
1844
handleEOF action =
1845
  catchJust
1846
    (\e -> if isEOFErrorType (ioeGetErrorType e) then Just () else Nothing)
1847
    (liftM Just action)
1848
    (\_ -> return Nothing)
1849

    
1850
-- | Server ping-pong helper.
1851
luxiServerPong :: Luxi.Client -> IO ()
1852
luxiServerPong c = do
1853
  msg <- handleEOF (Luxi.recvMsg c)
1854
  case msg of
1855
    Nothing -> return ()
1856
    Just m -> Luxi.sendMsg c m >> luxiServerPong c
1857

    
1858
-- | Client ping-pong helper.
1859
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1860
luxiClientPong c =
1861
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1862

    
1863
-- | Monadic check that, given a server socket, we can connect via a
1864
-- client to it, and that we can send a list of arbitrary messages and
1865
-- get back what we sent.
1866
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1867
prop_Luxi_ClientServer dnschars = monadicIO $ do
1868
  let msgs = map (map dnsGetChar) dnschars
1869
  fpath <- run $ getTempFileName
1870
  -- we need to create the server first, otherwise (if we do it in the
1871
  -- forked thread) the client could try to connect to it before it's
1872
  -- ready
1873
  server <- run $ Luxi.getServer fpath
1874
  -- fork the server responder
1875
  _ <- run $ forkIO $
1876
    bracket
1877
      (Luxi.acceptClient server)
1878
      (\c -> Luxi.closeClient c >> removeFile fpath)
1879
      luxiServerPong
1880
  replies <- run $
1881
    bracket
1882
      (Luxi.getClient fpath)
1883
      Luxi.closeClient
1884
      (\c -> luxiClientPong c msgs)
1885
  assert $ replies == msgs
1886

    
1887
testSuite "LUXI"
1888
          [ 'prop_Luxi_CallEncoding
1889
          , 'prop_Luxi_ClientServer
1890
          ]
1891

    
1892
-- * Ssconf tests
1893

    
1894
instance Arbitrary Ssconf.SSKey where
1895
  arbitrary = elements [minBound..maxBound]
1896

    
1897
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1898
prop_Ssconf_filename key =
1899
  printTestCase "Key doesn't start with correct prefix" $
1900
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1901

    
1902
testSuite "Ssconf"
1903
  [ 'prop_Ssconf_filename
1904
  ]