Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (75.2 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
  , testRpc
52
  ) where
53

    
54
import Test.QuickCheck
55
import Test.QuickCheck.Monadic (assert, monadicIO, run, stop)
56
import Text.Printf (printf)
57
import Data.List (intercalate, nub, isPrefixOf)
58
import Data.Maybe
59
import Control.Monad
60
import Control.Applicative
61
import qualified System.Console.GetOpt as GetOpt
62
import qualified Text.JSON as J
63
import qualified Data.Map
64
import qualified Data.IntMap as IntMap
65
import Control.Concurrent (forkIO)
66
import Control.Exception (bracket, catchJust)
67
import System.Directory (getTemporaryDirectory, removeFile)
68
import System.IO (hClose, openTempFile)
69
import System.IO.Error (isEOFErrorType, ioeGetErrorType)
70

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

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

    
111
import Ganeti.HTools.QCHelper (testSuite)
112

    
113
-- * Constants
114

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

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

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

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

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

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

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

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

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

    
178

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

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

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

    
190
-- * Helper functions
191

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

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

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

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

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

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

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

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

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

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

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

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

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

    
288
-- * Arbitrary instances
289

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
539
instance Arbitrary Objects.Hypervisor where
540
  arbitrary = elements [minBound..maxBound]
541

    
542
instance Arbitrary Objects.PartialNDParams where
543
  arbitrary = Objects.PartialNDParams <$> arbitrary
544

    
545
instance Arbitrary Objects.Node where
546
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
547
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
548
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
549
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
550

    
551
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
552
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
553

    
554
instance Arbitrary Rpc.RpcCallInstanceList where
555
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
556

    
557
instance Arbitrary Rpc.RpcCallNodeInfo where
558
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
559

    
560
-- * Actual tests
561

    
562
-- ** Utils tests
563

    
564
-- | Helper to generate a small string that doesn't contain commas.
565
genNonCommaString :: Gen [Char]
566
genNonCommaString = do
567
  size <- choose (0, 20) -- arbitrary max size
568
  vectorOf size (arbitrary `suchThat` ((/=) ','))
569

    
570
-- | If the list is not just an empty element, and if the elements do
571
-- not contain commas, then join+split should be idempotent.
572
prop_Utils_commaJoinSplit :: Property
573
prop_Utils_commaJoinSplit =
574
  forAll (choose (0, 20)) $ \llen ->
575
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
576
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
577

    
578
-- | Split and join should always be idempotent.
579
prop_Utils_commaSplitJoin :: [Char] -> Property
580
prop_Utils_commaSplitJoin s =
581
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
582

    
583
-- | fromObjWithDefault, we test using the Maybe monad and an integer
584
-- value.
585
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
586
prop_Utils_fromObjWithDefault def_value random_key =
587
  -- a missing key will be returned with the default
588
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
589
  -- a found key will be returned as is, not with default
590
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
591
       random_key (def_value+1) == Just def_value
592

    
593
-- | Test that functional if' behaves like the syntactic sugar if.
594
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
595
prop_Utils_if'if cnd a b =
596
  Utils.if' cnd a b ==? if cnd then a else b
597

    
598
-- | Test basic select functionality
599
prop_Utils_select :: Int      -- ^ Default result
600
                  -> [Int]    -- ^ List of False values
601
                  -> [Int]    -- ^ List of True values
602
                  -> Gen Prop -- ^ Test result
603
prop_Utils_select def lst1 lst2 =
604
  Utils.select def (flist ++ tlist) ==? expectedresult
605
    where expectedresult = Utils.if' (null lst2) def (head lst2)
606
          flist = zip (repeat False) lst1
607
          tlist = zip (repeat True)  lst2
608

    
609
-- | Test basic select functionality with undefined default
610
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
611
                         -> NonEmptyList Int -- ^ List of True values
612
                         -> Gen Prop         -- ^ Test result
613
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
614
  Utils.select undefined (flist ++ tlist) ==? head lst2
615
    where flist = zip (repeat False) lst1
616
          tlist = zip (repeat True)  lst2
617

    
618
-- | Test basic select functionality with undefined list values
619
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
620
                         -> NonEmptyList Int -- ^ List of True values
621
                         -> Gen Prop         -- ^ Test result
622
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
623
  Utils.select undefined cndlist ==? head lst2
624
    where flist = zip (repeat False) lst1
625
          tlist = zip (repeat True)  lst2
626
          cndlist = flist ++ tlist ++ [undefined]
627

    
628
prop_Utils_parseUnit :: NonNegative Int -> Property
629
prop_Utils_parseUnit (NonNegative n) =
630
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
631
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
632
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
633
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
634
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
635
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
636
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
637
  printTestCase "Internal error/overflow?"
638
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
639
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
640
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
641
        n_gb = n_mb * 1000
642
        n_tb = n_gb * 1000
643

    
644
-- | Test list for the Utils module.
645
testSuite "Utils"
646
            [ 'prop_Utils_commaJoinSplit
647
            , 'prop_Utils_commaSplitJoin
648
            , 'prop_Utils_fromObjWithDefault
649
            , 'prop_Utils_if'if
650
            , 'prop_Utils_select
651
            , 'prop_Utils_select_undefd
652
            , 'prop_Utils_select_undefv
653
            , 'prop_Utils_parseUnit
654
            ]
655

    
656
-- ** PeerMap tests
657

    
658
-- | Make sure add is idempotent.
659
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
660
                           -> PeerMap.Key -> PeerMap.Elem -> Property
661
prop_PeerMap_addIdempotent pmap key em =
662
  fn puniq ==? fn (fn puniq)
663
    where fn = PeerMap.add key em
664
          puniq = PeerMap.accumArray const pmap
665

    
666
-- | Make sure remove is idempotent.
667
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
668
prop_PeerMap_removeIdempotent pmap key =
669
  fn puniq ==? fn (fn puniq)
670
    where fn = PeerMap.remove key
671
          puniq = PeerMap.accumArray const pmap
672

    
673
-- | Make sure a missing item returns 0.
674
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
675
prop_PeerMap_findMissing pmap key =
676
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
677
    where puniq = PeerMap.accumArray const pmap
678

    
679
-- | Make sure an added item is found.
680
prop_PeerMap_addFind :: PeerMap.PeerMap
681
                     -> PeerMap.Key -> PeerMap.Elem -> Property
682
prop_PeerMap_addFind pmap key em =
683
  PeerMap.find key (PeerMap.add key em puniq) ==? em
684
    where puniq = PeerMap.accumArray const pmap
685

    
686
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
687
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
688
prop_PeerMap_maxElem pmap =
689
  PeerMap.maxElem puniq ==? if null puniq then 0
690
                              else (maximum . snd . unzip) puniq
691
    where puniq = PeerMap.accumArray const pmap
692

    
693
-- | List of tests for the PeerMap module.
694
testSuite "PeerMap"
695
            [ 'prop_PeerMap_addIdempotent
696
            , 'prop_PeerMap_removeIdempotent
697
            , 'prop_PeerMap_maxElem
698
            , 'prop_PeerMap_addFind
699
            , 'prop_PeerMap_findMissing
700
            ]
701

    
702
-- ** Container tests
703

    
704
-- we silence the following due to hlint bug fixed in later versions
705
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
706
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
707
prop_Container_addTwo cdata i1 i2 =
708
  fn i1 i2 cont == fn i2 i1 cont &&
709
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
710
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
711
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
712

    
713
prop_Container_nameOf :: Node.Node -> Property
714
prop_Container_nameOf node =
715
  let nl = makeSmallCluster node 1
716
      fnode = head (Container.elems nl)
717
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
718

    
719
-- | We test that in a cluster, given a random node, we can find it by
720
-- its name and alias, as long as all names and aliases are unique,
721
-- and that we fail to find a non-existing name.
722
prop_Container_findByName :: Property
723
prop_Container_findByName =
724
  forAll (genNode (Just 1) Nothing) $ \node ->
725
  forAll (choose (1, 20)) $ \ cnt ->
726
  forAll (choose (0, cnt - 1)) $ \ fidx ->
727
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
728
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
729
  let names = zip (take cnt allnames) (drop cnt allnames)
730
      nl = makeSmallCluster node cnt
731
      nodes = Container.elems nl
732
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
733
                                             nn { Node.name = name,
734
                                                  Node.alias = alias }))
735
               $ zip names nodes
736
      nl' = Container.fromList nodes'
737
      target = snd (nodes' !! fidx)
738
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
739
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
740
     printTestCase "Found non-existing name"
741
       (isNothing (Container.findByName nl' othername))
742

    
743
testSuite "Container"
744
            [ 'prop_Container_addTwo
745
            , 'prop_Container_nameOf
746
            , 'prop_Container_findByName
747
            ]
748

    
749
-- ** Instance tests
750

    
751
-- Simple instance tests, we only have setter/getters
752

    
753
prop_Instance_creat :: Instance.Instance -> Property
754
prop_Instance_creat inst =
755
  Instance.name inst ==? Instance.alias inst
756

    
757
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
758
prop_Instance_setIdx inst idx =
759
  Instance.idx (Instance.setIdx inst idx) ==? idx
760

    
761
prop_Instance_setName :: Instance.Instance -> String -> Bool
762
prop_Instance_setName inst name =
763
  Instance.name newinst == name &&
764
  Instance.alias newinst == name
765
    where newinst = Instance.setName inst name
766

    
767
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
768
prop_Instance_setAlias inst name =
769
  Instance.name newinst == Instance.name inst &&
770
  Instance.alias newinst == name
771
    where newinst = Instance.setAlias inst name
772

    
773
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
774
prop_Instance_setPri inst pdx =
775
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
776

    
777
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
778
prop_Instance_setSec inst sdx =
779
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
780

    
781
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
782
prop_Instance_setBoth inst pdx sdx =
783
  Instance.pNode si == pdx && Instance.sNode si == sdx
784
    where si = Instance.setBoth inst pdx sdx
785

    
786
prop_Instance_shrinkMG :: Instance.Instance -> Property
787
prop_Instance_shrinkMG inst =
788
  Instance.mem inst >= 2 * Types.unitMem ==>
789
    case Instance.shrinkByType inst Types.FailMem of
790
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
791
      _ -> False
792

    
793
prop_Instance_shrinkMF :: Instance.Instance -> Property
794
prop_Instance_shrinkMF inst =
795
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
796
    let inst' = inst { Instance.mem = mem}
797
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
798

    
799
prop_Instance_shrinkCG :: Instance.Instance -> Property
800
prop_Instance_shrinkCG inst =
801
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
802
    case Instance.shrinkByType inst Types.FailCPU of
803
      Types.Ok inst' ->
804
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
805
      _ -> False
806

    
807
prop_Instance_shrinkCF :: Instance.Instance -> Property
808
prop_Instance_shrinkCF inst =
809
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
810
    let inst' = inst { Instance.vcpus = vcpus }
811
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
812

    
813
prop_Instance_shrinkDG :: Instance.Instance -> Property
814
prop_Instance_shrinkDG inst =
815
  Instance.dsk inst >= 2 * Types.unitDsk ==>
816
    case Instance.shrinkByType inst Types.FailDisk of
817
      Types.Ok inst' ->
818
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
819
      _ -> False
820

    
821
prop_Instance_shrinkDF :: Instance.Instance -> Property
822
prop_Instance_shrinkDF inst =
823
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
824
    let inst' = inst { Instance.dsk = dsk }
825
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
826

    
827
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
828
prop_Instance_setMovable inst m =
829
  Instance.movable inst' ==? m
830
    where inst' = Instance.setMovable inst m
831

    
832
testSuite "Instance"
833
            [ 'prop_Instance_creat
834
            , 'prop_Instance_setIdx
835
            , 'prop_Instance_setName
836
            , 'prop_Instance_setAlias
837
            , 'prop_Instance_setPri
838
            , 'prop_Instance_setSec
839
            , 'prop_Instance_setBoth
840
            , 'prop_Instance_shrinkMG
841
            , 'prop_Instance_shrinkMF
842
            , 'prop_Instance_shrinkCG
843
            , 'prop_Instance_shrinkCF
844
            , 'prop_Instance_shrinkDG
845
            , 'prop_Instance_shrinkDF
846
            , 'prop_Instance_setMovable
847
            ]
848

    
849
-- ** Backends
850

    
851
-- *** Text backend tests
852

    
853
-- Instance text loader tests
854

    
855
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
856
                        -> NonEmptyList Char -> [Char]
857
                        -> NonNegative Int -> NonNegative Int -> Bool
858
                        -> Types.DiskTemplate -> Int -> Property
859
prop_Text_Load_Instance name mem dsk vcpus status
860
                        (NonEmpty pnode) snode
861
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
862
  pnode /= snode && pdx /= sdx ==>
863
  let vcpus_s = show vcpus
864
      dsk_s = show dsk
865
      mem_s = show mem
866
      su_s = show su
867
      status_s = Types.instanceStatusToRaw status
868
      ndx = if null snode
869
              then [(pnode, pdx)]
870
              else [(pnode, pdx), (snode, sdx)]
871
      nl = Data.Map.fromList ndx
872
      tags = ""
873
      sbal = if autobal then "Y" else "N"
874
      sdt = Types.diskTemplateToRaw dt
875
      inst = Text.loadInst nl
876
             [name, mem_s, dsk_s, vcpus_s, status_s,
877
              sbal, pnode, snode, sdt, tags, su_s]
878
      fail1 = Text.loadInst nl
879
              [name, mem_s, dsk_s, vcpus_s, status_s,
880
               sbal, pnode, pnode, tags]
881
  in case inst of
882
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
883
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
884
                                        \ loading the instance" $
885
               Instance.name i == name &&
886
               Instance.vcpus i == vcpus &&
887
               Instance.mem i == mem &&
888
               Instance.pNode i == pdx &&
889
               Instance.sNode i == (if null snode
890
                                      then Node.noSecondary
891
                                      else sdx) &&
892
               Instance.autoBalance i == autobal &&
893
               Instance.spindleUse i == su &&
894
               Types.isBad fail1
895

    
896
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
897
prop_Text_Load_InstanceFail ktn fields =
898
  length fields /= 10 && length fields /= 11 ==>
899
    case Text.loadInst nl fields of
900
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
901
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
902
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
903
    where nl = Data.Map.fromList ktn
904

    
905
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
906
                    -> Int -> Bool -> Bool
907
prop_Text_Load_Node name tm nm fm td fd tc fo =
908
  let conv v = if v < 0
909
                 then "?"
910
                 else show v
911
      tm_s = conv tm
912
      nm_s = conv nm
913
      fm_s = conv fm
914
      td_s = conv td
915
      fd_s = conv fd
916
      tc_s = conv tc
917
      fo_s = if fo
918
               then "Y"
919
               else "N"
920
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
921
      gid = Group.uuid defGroup
922
  in case Text.loadNode defGroupAssoc
923
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
924
       Nothing -> False
925
       Just (name', node) ->
926
         if fo || any_broken
927
           then Node.offline node
928
           else Node.name node == name' && name' == name &&
929
                Node.alias node == name &&
930
                Node.tMem node == fromIntegral tm &&
931
                Node.nMem node == nm &&
932
                Node.fMem node == fm &&
933
                Node.tDsk node == fromIntegral td &&
934
                Node.fDsk node == fd &&
935
                Node.tCpu node == fromIntegral tc
936

    
937
prop_Text_Load_NodeFail :: [String] -> Property
938
prop_Text_Load_NodeFail fields =
939
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
940

    
941
prop_Text_NodeLSIdempotent :: Property
942
prop_Text_NodeLSIdempotent =
943
  forAll (genNode (Just 1) Nothing) $ \node ->
944
  -- override failN1 to what loadNode returns by default
945
  let n = Node.setPolicy Types.defIPolicy $
946
          node { Node.failN1 = True, Node.offline = False }
947
  in
948
    (Text.loadNode defGroupAssoc.
949
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
950
    Just (Node.name n, n)
951

    
952
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
953
prop_Text_ISpecIdempotent ispec =
954
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
955
       Text.serializeISpec $ ispec of
956
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
957
    Types.Ok ispec' -> ispec ==? ispec'
958

    
959
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
960
prop_Text_IPolicyIdempotent ipol =
961
  case Text.loadIPolicy . Utils.sepSplit '|' $
962
       Text.serializeIPolicy owner ipol of
963
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
964
    Types.Ok res -> (owner, ipol) ==? res
965
  where owner = "dummy"
966

    
967
-- | This property, while being in the text tests, does more than just
968
-- test end-to-end the serialisation and loading back workflow; it
969
-- also tests the Loader.mergeData and the actuall
970
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
971
-- allocations, not for the business logic). As such, it's a quite
972
-- complex and slow test, and that's the reason we restrict it to
973
-- small cluster sizes.
974
prop_Text_CreateSerialise :: Property
975
prop_Text_CreateSerialise =
976
  forAll genTags $ \ctags ->
977
  forAll (choose (1, 20)) $ \maxiter ->
978
  forAll (choose (2, 10)) $ \count ->
979
  forAll genOnlineNode $ \node ->
980
  forAll (genInstanceSmallerThanNode node) $ \inst ->
981
  let nl = makeSmallCluster node count
982
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
983
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
984
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
985
     of
986
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
987
       Types.Ok (_, _, _, [], _) -> printTestCase
988
                                    "Failed to allocate: no allocations" False
989
       Types.Ok (_, nl', il', _, _) ->
990
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
991
                     Types.defIPolicy
992
             saved = Text.serializeCluster cdata
993
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
994
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
995
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
996
                ctags ==? ctags2 .&&.
997
                Types.defIPolicy ==? cpol2 .&&.
998
                il' ==? il2 .&&.
999
                defGroupList ==? gl2 .&&.
1000
                nl' ==? nl2
1001

    
1002
testSuite "Text"
1003
            [ 'prop_Text_Load_Instance
1004
            , 'prop_Text_Load_InstanceFail
1005
            , 'prop_Text_Load_Node
1006
            , 'prop_Text_Load_NodeFail
1007
            , 'prop_Text_NodeLSIdempotent
1008
            , 'prop_Text_ISpecIdempotent
1009
            , 'prop_Text_IPolicyIdempotent
1010
            , 'prop_Text_CreateSerialise
1011
            ]
1012

    
1013
-- *** Simu backend
1014

    
1015
-- | Generates a tuple of specs for simulation.
1016
genSimuSpec :: Gen (String, Int, Int, Int, Int)
1017
genSimuSpec = do
1018
  pol <- elements [C.allocPolicyPreferred,
1019
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
1020
                  "p", "a", "u"]
1021
 -- should be reasonable (nodes/group), bigger values only complicate
1022
 -- the display of failed tests, and we don't care (in this particular
1023
 -- test) about big node groups
1024
  nodes <- choose (0, 20)
1025
  dsk <- choose (0, maxDsk)
1026
  mem <- choose (0, maxMem)
1027
  cpu <- choose (0, maxCpu)
1028
  return (pol, nodes, dsk, mem, cpu)
1029

    
1030
-- | Checks that given a set of corrects specs, we can load them
1031
-- successfully, and that at high-level the values look right.
1032
prop_SimuLoad :: Property
1033
prop_SimuLoad =
1034
  forAll (choose (0, 10)) $ \ngroups ->
1035
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
1036
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
1037
                                          p n d m c::String) specs
1038
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
1039
      mdc_in = concatMap (\(_, n, d, m, c) ->
1040
                            replicate n (fromIntegral m, fromIntegral d,
1041
                                         fromIntegral c,
1042
                                         fromIntegral m, fromIntegral d))
1043
               specs :: [(Double, Double, Double, Int, Int)]
1044
  in case Simu.parseData strspecs of
1045
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1046
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1047
         let nodes = map snd $ IntMap.toAscList nl
1048
             nidx = map Node.idx nodes
1049
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1050
                                   Node.fMem n, Node.fDsk n)) nodes
1051
         in
1052
         Container.size gl ==? ngroups .&&.
1053
         Container.size nl ==? totnodes .&&.
1054
         Container.size il ==? 0 .&&.
1055
         length tags ==? 0 .&&.
1056
         ipol ==? Types.defIPolicy .&&.
1057
         nidx ==? [1..totnodes] .&&.
1058
         mdc_in ==? mdc_out .&&.
1059
         map Group.iPolicy (Container.elems gl) ==?
1060
             replicate ngroups Types.defIPolicy
1061

    
1062
testSuite "Simu"
1063
            [ 'prop_SimuLoad
1064
            ]
1065

    
1066
-- ** Node tests
1067

    
1068
prop_Node_setAlias :: Node.Node -> String -> Bool
1069
prop_Node_setAlias node name =
1070
  Node.name newnode == Node.name node &&
1071
  Node.alias newnode == name
1072
    where newnode = Node.setAlias node name
1073

    
1074
prop_Node_setOffline :: Node.Node -> Bool -> Property
1075
prop_Node_setOffline node status =
1076
  Node.offline newnode ==? status
1077
    where newnode = Node.setOffline node status
1078

    
1079
prop_Node_setXmem :: Node.Node -> Int -> Property
1080
prop_Node_setXmem node xm =
1081
  Node.xMem newnode ==? xm
1082
    where newnode = Node.setXmem node xm
1083

    
1084
prop_Node_setMcpu :: Node.Node -> Double -> Property
1085
prop_Node_setMcpu node mc =
1086
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1087
    where newnode = Node.setMcpu node mc
1088

    
1089
-- | Check that an instance add with too high memory or disk will be
1090
-- rejected.
1091
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1092
prop_Node_addPriFM node inst =
1093
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1094
  not (Instance.isOffline inst) ==>
1095
  case Node.addPri node inst'' of
1096
    Types.OpFail Types.FailMem -> True
1097
    _ -> False
1098
  where inst' = setInstanceSmallerThanNode node inst
1099
        inst'' = inst' { Instance.mem = Instance.mem inst }
1100

    
1101
-- | Check that adding a primary instance with too much disk fails
1102
-- with type FailDisk.
1103
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1104
prop_Node_addPriFD node inst =
1105
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1106
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1107
  let inst' = setInstanceSmallerThanNode node inst
1108
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1109
                     , Instance.diskTemplate = dt }
1110
  in case Node.addPri node inst'' of
1111
       Types.OpFail Types.FailDisk -> True
1112
       _ -> False
1113

    
1114
-- | Check that adding a primary instance with too many VCPUs fails
1115
-- with type FailCPU.
1116
prop_Node_addPriFC :: Property
1117
prop_Node_addPriFC =
1118
  forAll (choose (1, maxCpu)) $ \extra ->
1119
  forAll genOnlineNode $ \node ->
1120
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1121
  let inst' = setInstanceSmallerThanNode node inst
1122
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1123
  in case Node.addPri node inst'' of
1124
       Types.OpFail Types.FailCPU -> property True
1125
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1126

    
1127
-- | Check that an instance add with too high memory or disk will be
1128
-- rejected.
1129
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1130
prop_Node_addSec node inst pdx =
1131
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1132
    not (Instance.isOffline inst)) ||
1133
   Instance.dsk inst >= Node.fDsk node) &&
1134
  not (Node.failN1 node) ==>
1135
      isFailure (Node.addSec node inst pdx)
1136

    
1137
-- | Check that an offline instance with reasonable disk size but
1138
-- extra mem/cpu can always be added.
1139
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1140
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1141
  forAll genOnlineNode $ \node ->
1142
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1143
  let inst' = inst { Instance.runSt = Types.AdminOffline
1144
                   , Instance.mem = Node.availMem node + extra_mem
1145
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1146
  in case Node.addPri node inst' of
1147
       Types.OpGood _ -> property True
1148
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1149

    
1150
-- | Check that an offline instance with reasonable disk size but
1151
-- extra mem/cpu can always be added.
1152
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1153
                        -> Types.Ndx -> Property
1154
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1155
  forAll genOnlineNode $ \node ->
1156
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1157
  let inst' = inst { Instance.runSt = Types.AdminOffline
1158
                   , Instance.mem = Node.availMem node + extra_mem
1159
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1160
                   , Instance.diskTemplate = Types.DTDrbd8 }
1161
  in case Node.addSec node inst' pdx of
1162
       Types.OpGood _ -> property True
1163
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1164

    
1165
-- | Checks for memory reservation changes.
1166
prop_Node_rMem :: Instance.Instance -> Property
1167
prop_Node_rMem inst =
1168
  not (Instance.isOffline inst) ==>
1169
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1170
  -- ab = auto_balance, nb = non-auto_balance
1171
  -- we use -1 as the primary node of the instance
1172
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1173
                   , Instance.diskTemplate = Types.DTDrbd8 }
1174
      inst_ab = setInstanceSmallerThanNode node inst'
1175
      inst_nb = inst_ab { Instance.autoBalance = False }
1176
      -- now we have the two instances, identical except the
1177
      -- autoBalance attribute
1178
      orig_rmem = Node.rMem node
1179
      inst_idx = Instance.idx inst_ab
1180
      node_add_ab = Node.addSec node inst_ab (-1)
1181
      node_add_nb = Node.addSec node inst_nb (-1)
1182
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1183
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1184
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1185
       (Types.OpGood a_ab, Types.OpGood a_nb,
1186
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1187
         printTestCase "Consistency checks failed" $
1188
           Node.rMem a_ab >  orig_rmem &&
1189
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1190
           Node.rMem a_nb == orig_rmem &&
1191
           Node.rMem d_ab == orig_rmem &&
1192
           Node.rMem d_nb == orig_rmem &&
1193
           -- this is not related to rMem, but as good a place to
1194
           -- test as any
1195
           inst_idx `elem` Node.sList a_ab &&
1196
           inst_idx `notElem` Node.sList d_ab
1197
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1198

    
1199
-- | Check mdsk setting.
1200
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1201
prop_Node_setMdsk node mx =
1202
  Node.loDsk node' >= 0 &&
1203
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1204
  Node.availDisk node' >= 0 &&
1205
  Node.availDisk node' <= Node.fDsk node' &&
1206
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1207
  Node.mDsk node' == mx'
1208
    where node' = Node.setMdsk node mx'
1209
          SmallRatio mx' = mx
1210

    
1211
-- Check tag maps
1212
prop_Node_tagMaps_idempotent :: Property
1213
prop_Node_tagMaps_idempotent =
1214
  forAll genTags $ \tags ->
1215
  Node.delTags (Node.addTags m tags) tags ==? m
1216
    where m = Data.Map.empty
1217

    
1218
prop_Node_tagMaps_reject :: Property
1219
prop_Node_tagMaps_reject =
1220
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1221
  let m = Node.addTags Data.Map.empty tags
1222
  in all (\t -> Node.rejectAddTags m [t]) tags
1223

    
1224
prop_Node_showField :: Node.Node -> Property
1225
prop_Node_showField node =
1226
  forAll (elements Node.defaultFields) $ \ field ->
1227
  fst (Node.showHeader field) /= Types.unknownField &&
1228
  Node.showField node field /= Types.unknownField
1229

    
1230
prop_Node_computeGroups :: [Node.Node] -> Bool
1231
prop_Node_computeGroups nodes =
1232
  let ng = Node.computeGroups nodes
1233
      onlyuuid = map fst ng
1234
  in length nodes == sum (map (length . snd) ng) &&
1235
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1236
     length (nub onlyuuid) == length onlyuuid &&
1237
     (null nodes || not (null ng))
1238

    
1239
-- Check idempotence of add/remove operations
1240
prop_Node_addPri_idempotent :: Property
1241
prop_Node_addPri_idempotent =
1242
  forAll genOnlineNode $ \node ->
1243
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1244
  case Node.addPri node inst of
1245
    Types.OpGood node' -> Node.removePri node' inst ==? node
1246
    _ -> failTest "Can't add instance"
1247

    
1248
prop_Node_addSec_idempotent :: Property
1249
prop_Node_addSec_idempotent =
1250
  forAll genOnlineNode $ \node ->
1251
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1252
  let pdx = Node.idx node + 1
1253
      inst' = Instance.setPri inst pdx
1254
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1255
  in case Node.addSec node inst'' pdx of
1256
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1257
       _ -> failTest "Can't add instance"
1258

    
1259
testSuite "Node"
1260
            [ 'prop_Node_setAlias
1261
            , 'prop_Node_setOffline
1262
            , 'prop_Node_setMcpu
1263
            , 'prop_Node_setXmem
1264
            , 'prop_Node_addPriFM
1265
            , 'prop_Node_addPriFD
1266
            , 'prop_Node_addPriFC
1267
            , 'prop_Node_addSec
1268
            , 'prop_Node_addOfflinePri
1269
            , 'prop_Node_addOfflineSec
1270
            , 'prop_Node_rMem
1271
            , 'prop_Node_setMdsk
1272
            , 'prop_Node_tagMaps_idempotent
1273
            , 'prop_Node_tagMaps_reject
1274
            , 'prop_Node_showField
1275
            , 'prop_Node_computeGroups
1276
            , 'prop_Node_addPri_idempotent
1277
            , 'prop_Node_addSec_idempotent
1278
            ]
1279

    
1280
-- ** Cluster tests
1281

    
1282
-- | Check that the cluster score is close to zero for a homogeneous
1283
-- cluster.
1284
prop_Score_Zero :: Node.Node -> Property
1285
prop_Score_Zero node =
1286
  forAll (choose (1, 1024)) $ \count ->
1287
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1288
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1289
  let fn = Node.buildPeers node Container.empty
1290
      nlst = replicate count fn
1291
      score = Cluster.compCVNodes nlst
1292
  -- we can't say == 0 here as the floating point errors accumulate;
1293
  -- this should be much lower than the default score in CLI.hs
1294
  in score <= 1e-12
1295

    
1296
-- | Check that cluster stats are sane.
1297
prop_CStats_sane :: Property
1298
prop_CStats_sane =
1299
  forAll (choose (1, 1024)) $ \count ->
1300
  forAll genOnlineNode $ \node ->
1301
  let fn = Node.buildPeers node Container.empty
1302
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1303
      nl = Container.fromList nlst
1304
      cstats = Cluster.totalResources nl
1305
  in Cluster.csAdsk cstats >= 0 &&
1306
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1307

    
1308
-- | Check that one instance is allocated correctly, without
1309
-- rebalances needed.
1310
prop_ClusterAlloc_sane :: Instance.Instance -> Property
1311
prop_ClusterAlloc_sane inst =
1312
  forAll (choose (5, 20)) $ \count ->
1313
  forAll genOnlineNode $ \node ->
1314
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1315
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1316
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1317
     Cluster.tryAlloc nl il inst' of
1318
       Types.Bad _ -> False
1319
       Types.Ok as ->
1320
         case Cluster.asSolution as of
1321
           Nothing -> False
1322
           Just (xnl, xi, _, cv) ->
1323
             let il' = Container.add (Instance.idx xi) xi il
1324
                 tbl = Cluster.Table xnl il' cv []
1325
             in not (canBalance tbl True True False)
1326

    
1327
-- | Checks that on a 2-5 node cluster, we can allocate a random
1328
-- instance spec via tiered allocation (whatever the original instance
1329
-- spec), on either one or two nodes. Furthermore, we test that
1330
-- computed allocation statistics are correct.
1331
prop_ClusterCanTieredAlloc :: Instance.Instance -> Property
1332
prop_ClusterCanTieredAlloc inst =
1333
  forAll (choose (2, 5)) $ \count ->
1334
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1335
  let nl = makeSmallCluster node count
1336
      il = Container.empty
1337
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1338
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1339
  in case allocnodes >>= \allocnodes' ->
1340
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1341
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1342
       Types.Ok (_, nl', il', ixes, cstats) ->
1343
         let (ai_alloc, ai_pool, ai_unav) =
1344
               Cluster.computeAllocationDelta
1345
                (Cluster.totalResources nl)
1346
                (Cluster.totalResources nl')
1347
             all_nodes = Container.elems nl
1348
         in property (not (null ixes)) .&&.
1349
            IntMap.size il' ==? length ixes .&&.
1350
            length ixes ==? length cstats .&&.
1351
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1352
              sum (map Node.hiCpu all_nodes) .&&.
1353
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1354
              sum (map Node.tCpu all_nodes) .&&.
1355
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1356
              truncate (sum (map Node.tMem all_nodes)) .&&.
1357
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1358
              truncate (sum (map Node.tDsk all_nodes))
1359

    
1360
-- | Helper function to create a cluster with the given range of nodes
1361
-- and allocate an instance on it.
1362
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1363
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1364
genClusterAlloc count node inst =
1365
  let nl = makeSmallCluster node count
1366
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1367
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1368
     Cluster.tryAlloc nl Container.empty inst of
1369
       Types.Bad _ -> Types.Bad "Can't allocate"
1370
       Types.Ok as ->
1371
         case Cluster.asSolution as of
1372
           Nothing -> Types.Bad "Empty solution?"
1373
           Just (xnl, xi, _, _) ->
1374
             let xil = Container.add (Instance.idx xi) xi Container.empty
1375
             in Types.Ok (xnl, xil, xi)
1376

    
1377
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1378
-- we can also relocate it.
1379
prop_ClusterAllocRelocate :: Property
1380
prop_ClusterAllocRelocate =
1381
  forAll (choose (4, 8)) $ \count ->
1382
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1383
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1384
  case genClusterAlloc count node inst of
1385
    Types.Bad msg -> failTest msg
1386
    Types.Ok (nl, il, inst') ->
1387
      case IAlloc.processRelocate defGroupList nl il
1388
             (Instance.idx inst) 1
1389
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1390
                 then Instance.sNode
1391
                 else Instance.pNode) inst'] of
1392
        Types.Ok _ -> property True
1393
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1394

    
1395
-- | Helper property checker for the result of a nodeEvac or
1396
-- changeGroup operation.
1397
check_EvacMode :: Group.Group -> Instance.Instance
1398
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1399
               -> Property
1400
check_EvacMode grp inst result =
1401
  case result of
1402
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1403
    Types.Ok (_, _, es) ->
1404
      let moved = Cluster.esMoved es
1405
          failed = Cluster.esFailed es
1406
          opcodes = not . null $ Cluster.esOpCodes es
1407
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1408
         failmsg "'opcodes' is null" opcodes .&&.
1409
         case moved of
1410
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1411
                               .&&.
1412
                               failmsg "wrong target group"
1413
                                         (gdx == Group.idx grp)
1414
           v -> failmsg  ("invalid solution: " ++ show v) False
1415
  where failmsg :: String -> Bool -> Property
1416
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1417
        idx = Instance.idx inst
1418

    
1419
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1420
-- we can also node-evacuate it.
1421
prop_ClusterAllocEvacuate :: Property
1422
prop_ClusterAllocEvacuate =
1423
  forAll (choose (4, 8)) $ \count ->
1424
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1425
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1426
  case genClusterAlloc count node inst of
1427
    Types.Bad msg -> failTest msg
1428
    Types.Ok (nl, il, inst') ->
1429
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1430
                              Cluster.tryNodeEvac defGroupList nl il mode
1431
                                [Instance.idx inst']) .
1432
                              evacModeOptions .
1433
                              Instance.mirrorType $ inst'
1434

    
1435
-- | Checks that on a 4-8 node cluster with two node groups, once we
1436
-- allocate an instance on the first node group, we can also change
1437
-- its group.
1438
prop_ClusterAllocChangeGroup :: Property
1439
prop_ClusterAllocChangeGroup =
1440
  forAll (choose (4, 8)) $ \count ->
1441
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1442
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1443
  case genClusterAlloc count node inst of
1444
    Types.Bad msg -> failTest msg
1445
    Types.Ok (nl, il, inst') ->
1446
      -- we need to add a second node group and nodes to the cluster
1447
      let nl2 = Container.elems $ makeSmallCluster node count
1448
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1449
          maxndx = maximum . map Node.idx $ nl2
1450
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1451
                             , Node.idx = Node.idx n + maxndx }) nl2
1452
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1453
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1454
          nl' = IntMap.union nl nl4
1455
      in check_EvacMode grp2 inst' $
1456
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1457

    
1458
-- | Check that allocating multiple instances on a cluster, then
1459
-- adding an empty node, results in a valid rebalance.
1460
prop_ClusterAllocBalance :: Property
1461
prop_ClusterAllocBalance =
1462
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1463
  forAll (choose (3, 5)) $ \count ->
1464
  not (Node.offline node) && not (Node.failN1 node) ==>
1465
  let nl = makeSmallCluster node count
1466
      (hnode, nl') = IntMap.deleteFindMax nl
1467
      il = Container.empty
1468
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1469
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1470
  in case allocnodes >>= \allocnodes' ->
1471
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1472
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1473
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1474
       Types.Ok (_, xnl, il', _, _) ->
1475
         let ynl = Container.add (Node.idx hnode) hnode xnl
1476
             cv = Cluster.compCV ynl
1477
             tbl = Cluster.Table ynl il' cv []
1478
         in printTestCase "Failed to rebalance" $
1479
            canBalance tbl True True False
1480

    
1481
-- | Checks consistency.
1482
prop_ClusterCheckConsistency :: Node.Node -> Instance.Instance -> Bool
1483
prop_ClusterCheckConsistency node inst =
1484
  let nl = makeSmallCluster node 3
1485
      [node1, node2, node3] = Container.elems nl
1486
      node3' = node3 { Node.group = 1 }
1487
      nl' = Container.add (Node.idx node3') node3' nl
1488
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1489
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1490
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1491
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1492
  in null (ccheck [(0, inst1)]) &&
1493
     null (ccheck [(0, inst2)]) &&
1494
     (not . null $ ccheck [(0, inst3)])
1495

    
1496
-- | For now, we only test that we don't lose instances during the split.
1497
prop_ClusterSplitCluster :: Node.Node -> Instance.Instance -> Property
1498
prop_ClusterSplitCluster node inst =
1499
  forAll (choose (0, 100)) $ \icnt ->
1500
  let nl = makeSmallCluster node 2
1501
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1502
                   (nl, Container.empty) [1..icnt]
1503
      gni = Cluster.splitCluster nl' il'
1504
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1505
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1506
                                 (Container.elems nl'')) gni
1507

    
1508
-- | Helper function to check if we can allocate an instance on a
1509
-- given node list.
1510
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1511
canAllocOn nl reqnodes inst =
1512
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1513
       Cluster.tryAlloc nl (Container.empty) inst of
1514
       Types.Bad _ -> False
1515
       Types.Ok as ->
1516
         case Cluster.asSolution as of
1517
           Nothing -> False
1518
           Just _ -> True
1519

    
1520
-- | Checks that allocation obeys minimum and maximum instance
1521
-- policies. The unittest generates a random node, duplicates it /count/
1522
-- times, and generates a random instance that can be allocated on
1523
-- this mini-cluster; it then checks that after applying a policy that
1524
-- the instance doesn't fits, the allocation fails.
1525
prop_ClusterAllocPolicy :: Node.Node -> Property
1526
prop_ClusterAllocPolicy node =
1527
  -- rqn is the required nodes (1 or 2)
1528
  forAll (choose (1, 2)) $ \rqn ->
1529
  forAll (choose (5, 20)) $ \count ->
1530
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1531
         $ \inst ->
1532
  forAll (arbitrary `suchThat` (isFailure .
1533
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1534
  let node' = Node.setPolicy ipol node
1535
      nl = makeSmallCluster node' count
1536
  in not $ canAllocOn nl rqn inst
1537

    
1538
testSuite "Cluster"
1539
            [ 'prop_Score_Zero
1540
            , 'prop_CStats_sane
1541
            , 'prop_ClusterAlloc_sane
1542
            , 'prop_ClusterCanTieredAlloc
1543
            , 'prop_ClusterAllocRelocate
1544
            , 'prop_ClusterAllocEvacuate
1545
            , 'prop_ClusterAllocChangeGroup
1546
            , 'prop_ClusterAllocBalance
1547
            , 'prop_ClusterCheckConsistency
1548
            , 'prop_ClusterSplitCluster
1549
            , 'prop_ClusterAllocPolicy
1550
            ]
1551

    
1552
-- ** OpCodes tests
1553

    
1554
-- | Check that opcode serialization is idempotent.
1555
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1556
prop_OpCodes_serialization op =
1557
  case J.readJSON (J.showJSON op) of
1558
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1559
    J.Ok op' -> op ==? op'
1560

    
1561
testSuite "OpCodes"
1562
            [ 'prop_OpCodes_serialization ]
1563

    
1564
-- ** Jobs tests
1565

    
1566
-- | Check that (queued) job\/opcode status serialization is idempotent.
1567
prop_OpStatus_serialization :: Jobs.OpStatus -> Property
1568
prop_OpStatus_serialization os =
1569
  case J.readJSON (J.showJSON os) of
1570
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1571
    J.Ok os' -> os ==? os'
1572

    
1573
prop_JobStatus_serialization :: Jobs.JobStatus -> Property
1574
prop_JobStatus_serialization js =
1575
  case J.readJSON (J.showJSON js) of
1576
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1577
    J.Ok js' -> js ==? js'
1578

    
1579
testSuite "Jobs"
1580
            [ 'prop_OpStatus_serialization
1581
            , 'prop_JobStatus_serialization
1582
            ]
1583

    
1584
-- ** Loader tests
1585

    
1586
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1587
prop_Loader_lookupNode ktn inst node =
1588
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1589
    where nl = Data.Map.fromList ktn
1590

    
1591
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1592
prop_Loader_lookupInstance kti inst =
1593
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1594
    where il = Data.Map.fromList kti
1595

    
1596
prop_Loader_assignIndices :: Property
1597
prop_Loader_assignIndices =
1598
  -- generate nodes with unique names
1599
  forAll (arbitrary `suchThat`
1600
          (\nodes ->
1601
             let names = map Node.name nodes
1602
             in length names == length (nub names))) $ \nodes ->
1603
  let (nassoc, kt) =
1604
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1605
  in Data.Map.size nassoc == length nodes &&
1606
     Container.size kt == length nodes &&
1607
     if not (null nodes)
1608
       then maximum (IntMap.keys kt) == length nodes - 1
1609
       else True
1610

    
1611
-- | Checks that the number of primary instances recorded on the nodes
1612
-- is zero.
1613
prop_Loader_mergeData :: [Node.Node] -> Bool
1614
prop_Loader_mergeData ns =
1615
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1616
  in case Loader.mergeData [] [] [] []
1617
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1618
    Types.Bad _ -> False
1619
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1620
      let nodes = Container.elems nl
1621
          instances = Container.elems il
1622
      in (sum . map (length . Node.pList)) nodes == 0 &&
1623
         null instances
1624

    
1625
-- | Check that compareNameComponent on equal strings works.
1626
prop_Loader_compareNameComponent_equal :: String -> Bool
1627
prop_Loader_compareNameComponent_equal s =
1628
  BasicTypes.compareNameComponent s s ==
1629
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1630

    
1631
-- | Check that compareNameComponent on prefix strings works.
1632
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1633
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1634
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1635
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1636

    
1637
testSuite "Loader"
1638
            [ 'prop_Loader_lookupNode
1639
            , 'prop_Loader_lookupInstance
1640
            , 'prop_Loader_assignIndices
1641
            , 'prop_Loader_mergeData
1642
            , 'prop_Loader_compareNameComponent_equal
1643
            , 'prop_Loader_compareNameComponent_prefix
1644
            ]
1645

    
1646
-- ** Types tests
1647

    
1648
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1649
prop_Types_AllocPolicy_serialisation apol =
1650
  case J.readJSON (J.showJSON apol) of
1651
    J.Ok p -> p ==? apol
1652
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1653

    
1654
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1655
prop_Types_DiskTemplate_serialisation dt =
1656
  case J.readJSON (J.showJSON dt) of
1657
    J.Ok p -> p ==? dt
1658
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1659

    
1660
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1661
prop_Types_ISpec_serialisation ispec =
1662
  case J.readJSON (J.showJSON ispec) of
1663
    J.Ok p -> p ==? ispec
1664
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1665

    
1666
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1667
prop_Types_IPolicy_serialisation ipol =
1668
  case J.readJSON (J.showJSON ipol) of
1669
    J.Ok p -> p ==? ipol
1670
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1671

    
1672
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1673
prop_Types_EvacMode_serialisation em =
1674
  case J.readJSON (J.showJSON em) of
1675
    J.Ok p -> p ==? em
1676
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1677

    
1678
prop_Types_opToResult :: Types.OpResult Int -> Bool
1679
prop_Types_opToResult op =
1680
  case op of
1681
    Types.OpFail _ -> Types.isBad r
1682
    Types.OpGood v -> case r of
1683
                        Types.Bad _ -> False
1684
                        Types.Ok v' -> v == v'
1685
  where r = Types.opToResult op
1686

    
1687
prop_Types_eitherToResult :: Either String Int -> Bool
1688
prop_Types_eitherToResult ei =
1689
  case ei of
1690
    Left _ -> Types.isBad r
1691
    Right v -> case r of
1692
                 Types.Bad _ -> False
1693
                 Types.Ok v' -> v == v'
1694
    where r = Types.eitherToResult ei
1695

    
1696
testSuite "Types"
1697
            [ 'prop_Types_AllocPolicy_serialisation
1698
            , 'prop_Types_DiskTemplate_serialisation
1699
            , 'prop_Types_ISpec_serialisation
1700
            , 'prop_Types_IPolicy_serialisation
1701
            , 'prop_Types_EvacMode_serialisation
1702
            , 'prop_Types_opToResult
1703
            , 'prop_Types_eitherToResult
1704
            ]
1705

    
1706
-- ** CLI tests
1707

    
1708
-- | Test correct parsing.
1709
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1710
prop_CLI_parseISpec descr dsk mem cpu =
1711
  let str = printf "%d,%d,%d" dsk mem cpu::String
1712
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1713

    
1714
-- | Test parsing failure due to wrong section count.
1715
prop_CLI_parseISpecFail :: String -> Property
1716
prop_CLI_parseISpecFail descr =
1717
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1718
  forAll (replicateM nelems arbitrary) $ \values ->
1719
  let str = intercalate "," $ map show (values::[Int])
1720
  in case CLI.parseISpecString descr str of
1721
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1722
       _ -> property True
1723

    
1724
-- | Test parseYesNo.
1725
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1726
prop_CLI_parseYesNo def testval val =
1727
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1728
  if testval
1729
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1730
    else let result = CLI.parseYesNo def (Just actual_val)
1731
         in if actual_val `elem` ["yes", "no"]
1732
              then result ==? Types.Ok (actual_val == "yes")
1733
              else property $ Types.isBad result
1734

    
1735
-- | Helper to check for correct parsing of string arg.
1736
checkStringArg :: [Char]
1737
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1738
                   CLI.Options -> Maybe [Char])
1739
               -> Property
1740
checkStringArg val (opt, fn) =
1741
  let GetOpt.Option _ longs _ _ = opt
1742
  in case longs of
1743
       [] -> failTest "no long options?"
1744
       cmdarg:_ ->
1745
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1746
           Left e -> failTest $ "Failed to parse option: " ++ show e
1747
           Right (options, _) -> fn options ==? Just val
1748

    
1749
-- | Test a few string arguments.
1750
prop_CLI_StringArg :: [Char] -> Property
1751
prop_CLI_StringArg argument =
1752
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1753
             , (CLI.oDynuFile,      CLI.optDynuFile)
1754
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1755
             , (CLI.oReplay,        CLI.optReplay)
1756
             , (CLI.oPrintCommands, CLI.optShowCmds)
1757
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1758
             ]
1759
  in conjoin $ map (checkStringArg argument) args
1760

    
1761
-- | Helper to test that a given option is accepted OK with quick exit.
1762
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1763
checkEarlyExit name options param =
1764
  case CLI.parseOptsInner [param] name options of
1765
    Left (code, _) -> if code == 0
1766
                          then property True
1767
                          else failTest $ "Program " ++ name ++
1768
                                 " returns invalid code " ++ show code ++
1769
                                 " for option " ++ param
1770
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1771
         param ++ " as early exit one"
1772

    
1773
-- | Test that all binaries support some common options. There is
1774
-- nothing actually random about this test...
1775
prop_CLI_stdopts :: Property
1776
prop_CLI_stdopts =
1777
  let params = ["-h", "--help", "-V", "--version"]
1778
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1779
      -- apply checkEarlyExit across the cartesian product of params and opts
1780
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1781

    
1782
testSuite "CLI"
1783
          [ 'prop_CLI_parseISpec
1784
          , 'prop_CLI_parseISpecFail
1785
          , 'prop_CLI_parseYesNo
1786
          , 'prop_CLI_StringArg
1787
          , 'prop_CLI_stdopts
1788
          ]
1789

    
1790
-- * JSON tests
1791

    
1792
prop_JSON_toArray :: [Int] -> Property
1793
prop_JSON_toArray intarr =
1794
  let arr = map J.showJSON intarr in
1795
  case JSON.toArray (J.JSArray arr) of
1796
    Types.Ok arr' -> arr ==? arr'
1797
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1798

    
1799
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1800
prop_JSON_toArrayFail i s b =
1801
  -- poor man's instance Arbitrary JSValue
1802
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1803
  case JSON.toArray item of
1804
    Types.Bad _ -> property True
1805
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1806

    
1807
testSuite "JSON"
1808
          [ 'prop_JSON_toArray
1809
          , 'prop_JSON_toArrayFail
1810
          ]
1811

    
1812
-- * Luxi tests
1813

    
1814
instance Arbitrary Luxi.LuxiReq where
1815
  arbitrary = elements [minBound..maxBound]
1816

    
1817
instance Arbitrary Luxi.QrViaLuxi where
1818
  arbitrary = elements [minBound..maxBound]
1819

    
1820
instance Arbitrary Luxi.LuxiOp where
1821
  arbitrary = do
1822
    lreq <- arbitrary
1823
    case lreq of
1824
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> arbitrary
1825
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1826
                            getFields <*> arbitrary
1827
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1828
                             arbitrary <*> arbitrary
1829
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1830
                                getFields <*> arbitrary
1831
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1832
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1833
                              (listOf getFQDN) <*> arbitrary
1834
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1835
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1836
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> getName <*> getFQDN
1837
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1838
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1839
                                (resize maxOpCodes arbitrary)
1840
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1841
                                  getFields <*> pure J.JSNull <*>
1842
                                  pure J.JSNull <*> arbitrary
1843
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1844
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1845
                                 arbitrary
1846
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1847
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1848
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1849

    
1850
-- | Simple check that encoding/decoding of LuxiOp works.
1851
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1852
prop_Luxi_CallEncoding op =
1853
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1854

    
1855
-- | Helper to a get a temporary file name.
1856
getTempFileName :: IO FilePath
1857
getTempFileName = do
1858
  tempdir <- getTemporaryDirectory
1859
  (fpath, handle) <- openTempFile tempdir "luxitest"
1860
  _ <- hClose handle
1861
  removeFile fpath
1862
  return fpath
1863

    
1864
-- | Helper to execute recvMsg but return Nothing if we reach EOF.
1865
handleEOF :: (IO a) -> IO (Maybe a)
1866
handleEOF action =
1867
  catchJust
1868
    (\e -> if isEOFErrorType (ioeGetErrorType e) then Just () else Nothing)
1869
    (liftM Just action)
1870
    (\_ -> return Nothing)
1871

    
1872
-- | Server ping-pong helper.
1873
luxiServerPong :: Luxi.Client -> IO ()
1874
luxiServerPong c = do
1875
  msg <- handleEOF (Luxi.recvMsg c)
1876
  case msg of
1877
    Nothing -> return ()
1878
    Just m -> Luxi.sendMsg c m >> luxiServerPong c
1879

    
1880
-- | Client ping-pong helper.
1881
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1882
luxiClientPong c =
1883
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1884

    
1885
-- | Monadic check that, given a server socket, we can connect via a
1886
-- client to it, and that we can send a list of arbitrary messages and
1887
-- get back what we sent.
1888
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1889
prop_Luxi_ClientServer dnschars = monadicIO $ do
1890
  let msgs = map (map dnsGetChar) dnschars
1891
  fpath <- run $ getTempFileName
1892
  -- we need to create the server first, otherwise (if we do it in the
1893
  -- forked thread) the client could try to connect to it before it's
1894
  -- ready
1895
  server <- run $ Luxi.getServer fpath
1896
  -- fork the server responder
1897
  _ <- run $ forkIO $
1898
    bracket
1899
      (Luxi.acceptClient server)
1900
      (\c -> Luxi.closeClient c >> removeFile fpath)
1901
      luxiServerPong
1902
  replies <- run $
1903
    bracket
1904
      (Luxi.getClient fpath)
1905
      Luxi.closeClient
1906
      (\c -> luxiClientPong c msgs)
1907
  assert $ replies == msgs
1908

    
1909
testSuite "LUXI"
1910
          [ 'prop_Luxi_CallEncoding
1911
          , 'prop_Luxi_ClientServer
1912
          ]
1913

    
1914
-- * Ssconf tests
1915

    
1916
instance Arbitrary Ssconf.SSKey where
1917
  arbitrary = elements [minBound..maxBound]
1918

    
1919
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1920
prop_Ssconf_filename key =
1921
  printTestCase "Key doesn't start with correct prefix" $
1922
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1923

    
1924
testSuite "Ssconf"
1925
  [ 'prop_Ssconf_filename
1926
  ]
1927

    
1928
-- * Rpc tests
1929

    
1930
-- | Monadic check that, for an offline node and a call that does not
1931
-- offline nodes, we get a OfflineNodeError response.
1932
-- FIXME: We need a way of generalizing this, running it for
1933
-- every call manually will soon get problematic
1934
prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
1935
prop_Rpc_noffl_request_allinstinfo call =
1936
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1937
      res <- run $ Rpc.executeRpcCall [node] call
1938
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1939

    
1940
prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
1941
prop_Rpc_noffl_request_instlist call =
1942
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1943
      res <- run $ Rpc.executeRpcCall [node] call
1944
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1945

    
1946
prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
1947
prop_Rpc_noffl_request_nodeinfo call =
1948
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1949
      res <- run $ Rpc.executeRpcCall [node] call
1950
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1951

    
1952
testSuite "Rpc"
1953
  [ 'prop_Rpc_noffl_request_allinstinfo
1954
  , 'prop_Rpc_noffl_request_instlist
1955
  , 'prop_Rpc_noffl_request_nodeinfo
1956
  ]