Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 66f74cae

History | View | Annotate | Download (75.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
  , 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.Node where
543
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
544
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
545
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
546
              <*> arbitrary <*> getFQDN  <*> arbitrary
547

    
548
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
549
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
550

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

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

    
557
-- * Actual tests
558

    
559
-- ** Utils tests
560

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

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

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

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

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

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

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

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

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

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

    
653
-- ** PeerMap tests
654

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

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

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

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

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

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

    
699
-- ** Container tests
700

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

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

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

    
740
testSuite "Container"
741
            [ 'prop_Container_addTwo
742
            , 'prop_Container_nameOf
743
            , 'prop_Container_findByName
744
            ]
745

    
746
-- ** Instance tests
747

    
748
-- Simple instance tests, we only have setter/getters
749

    
750
prop_Instance_creat :: Instance.Instance -> Property
751
prop_Instance_creat inst =
752
  Instance.name inst ==? Instance.alias inst
753

    
754
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
755
prop_Instance_setIdx inst idx =
756
  Instance.idx (Instance.setIdx inst idx) ==? idx
757

    
758
prop_Instance_setName :: Instance.Instance -> String -> Bool
759
prop_Instance_setName inst name =
760
  Instance.name newinst == name &&
761
  Instance.alias newinst == name
762
    where newinst = Instance.setName inst name
763

    
764
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
765
prop_Instance_setAlias inst name =
766
  Instance.name newinst == Instance.name inst &&
767
  Instance.alias newinst == name
768
    where newinst = Instance.setAlias inst name
769

    
770
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
771
prop_Instance_setPri inst pdx =
772
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
773

    
774
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
775
prop_Instance_setSec inst sdx =
776
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
777

    
778
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
779
prop_Instance_setBoth inst pdx sdx =
780
  Instance.pNode si == pdx && Instance.sNode si == sdx
781
    where si = Instance.setBoth inst pdx sdx
782

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

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

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

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

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

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

    
824
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
825
prop_Instance_setMovable inst m =
826
  Instance.movable inst' ==? m
827
    where inst' = Instance.setMovable inst m
828

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

    
846
-- ** Backends
847

    
848
-- *** Text backend tests
849

    
850
-- Instance text loader tests
851

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

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

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

    
934
prop_Text_Load_NodeFail :: [String] -> Property
935
prop_Text_Load_NodeFail fields =
936
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
937

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

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

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

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

    
999
testSuite "Text"
1000
            [ 'prop_Text_Load_Instance
1001
            , 'prop_Text_Load_InstanceFail
1002
            , 'prop_Text_Load_Node
1003
            , 'prop_Text_Load_NodeFail
1004
            , 'prop_Text_NodeLSIdempotent
1005
            , 'prop_Text_ISpecIdempotent
1006
            , 'prop_Text_IPolicyIdempotent
1007
            , 'prop_Text_CreateSerialise
1008
            ]
1009

    
1010
-- *** Simu backend
1011

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

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

    
1059
testSuite "Simu"
1060
            [ 'prop_SimuLoad
1061
            ]
1062

    
1063
-- ** Node tests
1064

    
1065
prop_Node_setAlias :: Node.Node -> String -> Bool
1066
prop_Node_setAlias node name =
1067
  Node.name newnode == Node.name node &&
1068
  Node.alias newnode == name
1069
    where newnode = Node.setAlias node name
1070

    
1071
prop_Node_setOffline :: Node.Node -> Bool -> Property
1072
prop_Node_setOffline node status =
1073
  Node.offline newnode ==? status
1074
    where newnode = Node.setOffline node status
1075

    
1076
prop_Node_setXmem :: Node.Node -> Int -> Property
1077
prop_Node_setXmem node xm =
1078
  Node.xMem newnode ==? xm
1079
    where newnode = Node.setXmem node xm
1080

    
1081
prop_Node_setMcpu :: Node.Node -> Double -> Property
1082
prop_Node_setMcpu node mc =
1083
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1084
    where newnode = Node.setMcpu node mc
1085

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1277
-- ** Cluster tests
1278

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1549
-- ** OpCodes tests
1550

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

    
1558
testSuite "OpCodes"
1559
            [ 'prop_OpCodes_serialization ]
1560

    
1561
-- ** Jobs tests
1562

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

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

    
1576
testSuite "Jobs"
1577
            [ 'prop_OpStatus_serialization
1578
            , 'prop_JobStatus_serialization
1579
            ]
1580

    
1581
-- ** Loader tests
1582

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

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

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

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

    
1622
-- | Check that compareNameComponent on equal strings works.
1623
prop_Loader_compareNameComponent_equal :: String -> Bool
1624
prop_Loader_compareNameComponent_equal s =
1625
  BasicTypes.compareNameComponent s s ==
1626
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1627

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

    
1634
testSuite "Loader"
1635
            [ 'prop_Loader_lookupNode
1636
            , 'prop_Loader_lookupInstance
1637
            , 'prop_Loader_assignIndices
1638
            , 'prop_Loader_mergeData
1639
            , 'prop_Loader_compareNameComponent_equal
1640
            , 'prop_Loader_compareNameComponent_prefix
1641
            ]
1642

    
1643
-- ** Types tests
1644

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

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

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

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

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

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

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

    
1693
testSuite "Types"
1694
            [ 'prop_Types_AllocPolicy_serialisation
1695
            , 'prop_Types_DiskTemplate_serialisation
1696
            , 'prop_Types_ISpec_serialisation
1697
            , 'prop_Types_IPolicy_serialisation
1698
            , 'prop_Types_EvacMode_serialisation
1699
            , 'prop_Types_opToResult
1700
            , 'prop_Types_eitherToResult
1701
            ]
1702

    
1703
-- ** CLI tests
1704

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

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

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

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

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

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

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

    
1779
testSuite "CLI"
1780
          [ 'prop_CLI_parseISpec
1781
          , 'prop_CLI_parseISpecFail
1782
          , 'prop_CLI_parseYesNo
1783
          , 'prop_CLI_StringArg
1784
          , 'prop_CLI_stdopts
1785
          ]
1786

    
1787
-- * JSON tests
1788

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

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

    
1804
testSuite "JSON"
1805
          [ 'prop_JSON_toArray
1806
          , 'prop_JSON_toArrayFail
1807
          ]
1808

    
1809
-- * Luxi tests
1810

    
1811
instance Arbitrary Luxi.LuxiReq where
1812
  arbitrary = elements [minBound..maxBound]
1813

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

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

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

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

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

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

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

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

    
1906
testSuite "LUXI"
1907
          [ 'prop_Luxi_CallEncoding
1908
          , 'prop_Luxi_ClientServer
1909
          ]
1910

    
1911
-- * Ssconf tests
1912

    
1913
instance Arbitrary Ssconf.SSKey where
1914
  arbitrary = elements [minBound..maxBound]
1915

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

    
1921
testSuite "Ssconf"
1922
  [ 'prop_Ssconf_filename
1923
  ]
1924

    
1925
-- * Rpc tests
1926

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

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

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

    
1949
testSuite "Rpc"
1950
  [ 'prop_Rpc_noffl_request_allinstinfo
1951
  , 'prop_Rpc_noffl_request_instlist
1952
  , 'prop_Rpc_noffl_request_nodeinfo
1953
  ]