Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 4cab6703

History | View | Annotate | Download (84.9 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
  , testQlang
53
  , testConfd
54
  , testObjects
55
  ) where
56

    
57
import qualified Test.HUnit as HUnit
58
import Test.QuickCheck
59
import Test.QuickCheck.Monadic (assert, monadicIO, run, stop)
60
import Text.Printf (printf)
61
import Data.List (intercalate, nub, isPrefixOf, sort, (\\))
62
import Data.Maybe
63
import qualified Data.Set as Set
64
import Control.Monad
65
import Control.Applicative
66
import qualified System.Console.GetOpt as GetOpt
67
import qualified Text.JSON as J
68
import qualified Data.Map as Map
69
import qualified Data.IntMap as IntMap
70
import Control.Concurrent (forkIO)
71
import Control.Exception (bracket, catchJust)
72
import System.Directory (getTemporaryDirectory, removeFile)
73
import System.Environment (getEnv)
74
import System.Exit (ExitCode(..))
75
import System.IO (hClose, openTempFile)
76
import System.IO.Error (isEOFErrorType, ioeGetErrorType, isDoesNotExistError)
77
import System.Process (readProcessWithExitCode)
78

    
79
import qualified Ganeti.Confd as Confd
80
import qualified Ganeti.Confd.Server as Confd.Server
81
import qualified Ganeti.Confd.Utils as Confd.Utils
82
import qualified Ganeti.Config as Config
83
import qualified Ganeti.Daemon as Daemon
84
import qualified Ganeti.Hash as Hash
85
import qualified Ganeti.BasicTypes as BasicTypes
86
import qualified Ganeti.Jobs as Jobs
87
import qualified Ganeti.Logging as Logging
88
import qualified Ganeti.Luxi as Luxi
89
import qualified Ganeti.Objects as Objects
90
import qualified Ganeti.OpCodes as OpCodes
91
import qualified Ganeti.Rpc as Rpc
92
import qualified Ganeti.Query.Language as Qlang
93
import qualified Ganeti.Runtime as Runtime
94
import qualified Ganeti.Ssconf as Ssconf
95
import qualified Ganeti.HTools.CLI as CLI
96
import qualified Ganeti.HTools.Cluster as Cluster
97
import qualified Ganeti.HTools.Container as Container
98
import qualified Ganeti.HTools.ExtLoader
99
import qualified Ganeti.HTools.Group as Group
100
import qualified Ganeti.HTools.IAlloc as IAlloc
101
import qualified Ganeti.HTools.Instance as Instance
102
import qualified Ganeti.HTools.JSON as JSON
103
import qualified Ganeti.HTools.Loader as Loader
104
import qualified Ganeti.HTools.Luxi as HTools.Luxi
105
import qualified Ganeti.HTools.Node as Node
106
import qualified Ganeti.HTools.PeerMap as PeerMap
107
import qualified Ganeti.HTools.Rapi
108
import qualified Ganeti.HTools.Simu as Simu
109
import qualified Ganeti.HTools.Text as Text
110
import qualified Ganeti.HTools.Types as Types
111
import qualified Ganeti.HTools.Utils as Utils
112
import qualified Ganeti.HTools.Version
113
import qualified Ganeti.Constants as C
114

    
115
import qualified Ganeti.HTools.Program as Program
116
import qualified Ganeti.HTools.Program.Hail
117
import qualified Ganeti.HTools.Program.Hbal
118
import qualified Ganeti.HTools.Program.Hscan
119
import qualified Ganeti.HTools.Program.Hspace
120

    
121
import Ganeti.HTools.QCHelper (testSuite)
122

    
123
-- * Constants
124

    
125
-- | Maximum memory (1TiB, somewhat random value).
126
maxMem :: Int
127
maxMem = 1024 * 1024
128

    
129
-- | Maximum disk (8TiB, somewhat random value).
130
maxDsk :: Int
131
maxDsk = 1024 * 1024 * 8
132

    
133
-- | Max CPUs (1024, somewhat random value).
134
maxCpu :: Int
135
maxCpu = 1024
136

    
137
-- | Max vcpu ratio (random value).
138
maxVcpuRatio :: Double
139
maxVcpuRatio = 1024.0
140

    
141
-- | Max spindle ratio (random value).
142
maxSpindleRatio :: Double
143
maxSpindleRatio = 1024.0
144

    
145
-- | Max nodes, used just to limit arbitrary instances for smaller
146
-- opcode definitions (e.g. list of nodes in OpTestDelay).
147
maxNodes :: Int
148
maxNodes = 32
149

    
150
-- | Max opcodes or jobs in a submit job and submit many jobs.
151
maxOpCodes :: Int
152
maxOpCodes = 16
153

    
154
-- | All disk templates (used later)
155
allDiskTemplates :: [Types.DiskTemplate]
156
allDiskTemplates = [minBound..maxBound]
157

    
158
-- | Null iPolicy, and by null we mean very liberal.
159
nullIPolicy :: Types.IPolicy
160
nullIPolicy = Types.IPolicy
161
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
162
                                       , Types.iSpecCpuCount   = 0
163
                                       , Types.iSpecDiskSize   = 0
164
                                       , Types.iSpecDiskCount  = 0
165
                                       , Types.iSpecNicCount   = 0
166
                                       , Types.iSpecSpindleUse = 0
167
                                       }
168
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
169
                                       , Types.iSpecCpuCount   = maxBound
170
                                       , Types.iSpecDiskSize   = maxBound
171
                                       , Types.iSpecDiskCount  = C.maxDisks
172
                                       , Types.iSpecNicCount   = C.maxNics
173
                                       , Types.iSpecSpindleUse = maxBound
174
                                       }
175
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
176
                                       , Types.iSpecCpuCount   = Types.unitCpu
177
                                       , Types.iSpecDiskSize   = Types.unitDsk
178
                                       , Types.iSpecDiskCount  = 1
179
                                       , Types.iSpecNicCount   = 1
180
                                       , Types.iSpecSpindleUse = 1
181
                                       }
182
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
183
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
184
                                          -- enough to not impact us
185
  , Types.iPolicySpindleRatio = maxSpindleRatio
186
  }
187

    
188

    
189
defGroup :: Group.Group
190
defGroup = flip Group.setIdx 0 $
191
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
192
                  nullIPolicy
193

    
194
defGroupList :: Group.List
195
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
196

    
197
defGroupAssoc :: Map.Map String Types.Gdx
198
defGroupAssoc = Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
199

    
200
-- * Helper functions
201

    
202
-- | Simple checker for whether OpResult is fail or pass.
203
isFailure :: Types.OpResult a -> Bool
204
isFailure (Types.OpFail _) = True
205
isFailure _ = False
206

    
207
-- | Checks for equality with proper annotation.
208
(==?) :: (Show a, Eq a) => a -> a -> Property
209
(==?) x y = printTestCase
210
            ("Expected equality, but '" ++
211
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
212
infix 3 ==?
213

    
214
-- | Show a message and fail the test.
215
failTest :: String -> Property
216
failTest msg = printTestCase msg False
217

    
218
-- | Return the python binary to use. If the PYTHON environment
219
-- variable is defined, use its value, otherwise use just \"python\".
220
pythonCmd :: IO String
221
pythonCmd = catchJust (guard . isDoesNotExistError)
222
            (getEnv "PYTHON") (const (return "python"))
223

    
224
-- | Run Python with an expression, returning the exit code, standard
225
-- output and error.
226
runPython :: String -> String -> IO (ExitCode, String, String)
227
runPython expr stdin = do
228
  py_binary <- pythonCmd
229
  readProcessWithExitCode py_binary ["-c", expr] stdin
230

    
231
-- | Check python exit code, and fail via HUnit assertions if
232
-- non-zero. Otherwise, return the standard output.
233
checkPythonResult :: (ExitCode, String, String) -> IO String
234
checkPythonResult (py_code, py_stdout, py_stderr) = do
235
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
236
       ExitSuccess py_code
237
  return py_stdout
238

    
239
-- | Update an instance to be smaller than a node.
240
setInstanceSmallerThanNode :: Node.Node
241
                           -> Instance.Instance -> Instance.Instance
242
setInstanceSmallerThanNode node inst =
243
  inst { Instance.mem = Node.availMem node `div` 2
244
       , Instance.dsk = Node.availDisk node `div` 2
245
       , Instance.vcpus = Node.availCpu node `div` 2
246
       }
247

    
248
-- | Create an instance given its spec.
249
createInstance :: Int -> Int -> Int -> Instance.Instance
250
createInstance mem dsk vcpus =
251
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
252
    Types.DTDrbd8 1
253

    
254
-- | Create a small cluster by repeating a node spec.
255
makeSmallCluster :: Node.Node -> Int -> Node.List
256
makeSmallCluster node count =
257
  let origname = Node.name node
258
      origalias = Node.alias node
259
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
260
                                , Node.alias = origalias ++ "-" ++ show idx })
261
              [1..count]
262
      fn = flip Node.buildPeers Container.empty
263
      namelst = map (\n -> (Node.name n, fn n)) nodes
264
      (_, nlst) = Loader.assignIndices namelst
265
  in nlst
266

    
267
-- | Make a small cluster, both nodes and instances.
268
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
269
                      -> (Node.List, Instance.List, Instance.Instance)
270
makeSmallEmptyCluster node count inst =
271
  (makeSmallCluster node count, Container.empty,
272
   setInstanceSmallerThanNode node inst)
273

    
274
-- | Checks if a node is "big" enough.
275
isNodeBig :: Int -> Node.Node -> Bool
276
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
277
                      && Node.availMem node > size * Types.unitMem
278
                      && Node.availCpu node > size * Types.unitCpu
279

    
280
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
281
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
282

    
283
-- | Assigns a new fresh instance to a cluster; this is not
284
-- allocation, so no resource checks are done.
285
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
286
                  Types.Idx -> Types.Idx ->
287
                  (Node.List, Instance.List)
288
assignInstance nl il inst pdx sdx =
289
  let pnode = Container.find pdx nl
290
      snode = Container.find sdx nl
291
      maxiidx = if Container.null il
292
                  then 0
293
                  else fst (Container.findMax il) + 1
294
      inst' = inst { Instance.idx = maxiidx,
295
                     Instance.pNode = pdx, Instance.sNode = sdx }
296
      pnode' = Node.setPri pnode inst'
297
      snode' = Node.setSec snode inst'
298
      nl' = Container.addTwo pdx pnode' sdx snode' nl
299
      il' = Container.add maxiidx inst' il
300
  in (nl', il')
301

    
302
-- | Generates a list of a given size with non-duplicate elements.
303
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
304
genUniquesList cnt =
305
  foldM (\lst _ -> do
306
           newelem <- arbitrary `suchThat` (`notElem` lst)
307
           return (newelem:lst)) [] [1..cnt]
308

    
309
-- | Checks if an instance is mirrored.
310
isMirrored :: Instance.Instance -> Bool
311
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
312

    
313
-- | Returns the possible change node types for a disk template.
314
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
315
evacModeOptions Types.MirrorNone     = []
316
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
317
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
318

    
319
-- * Arbitrary instances
320

    
321
-- | Defines a DNS name.
322
newtype DNSChar = DNSChar { dnsGetChar::Char }
323

    
324
instance Arbitrary DNSChar where
325
  arbitrary = do
326
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
327
    return (DNSChar x)
328

    
329
instance Show DNSChar where
330
  show = show . dnsGetChar
331

    
332
-- | Generates a single name component.
333
getName :: Gen String
334
getName = do
335
  n <- choose (1, 64)
336
  dn <- vector n
337
  return (map dnsGetChar dn)
338

    
339
-- | Generates an entire FQDN.
340
getFQDN :: Gen String
341
getFQDN = do
342
  ncomps <- choose (1, 4)
343
  names <- vectorOf ncomps getName
344
  return $ intercalate "." names
345

    
346
-- | Combinator that generates a 'Maybe' using a sub-combinator.
347
getMaybe :: Gen a -> Gen (Maybe a)
348
getMaybe subgen = do
349
  bool <- arbitrary
350
  if bool
351
    then Just <$> subgen
352
    else return Nothing
353

    
354
-- | Generates a fields list. This uses the same character set as a
355
-- DNS name (just for simplicity).
356
getFields :: Gen [String]
357
getFields = do
358
  n <- choose (1, 32)
359
  vectorOf n getName
360

    
361
-- | Defines a tag type.
362
newtype TagChar = TagChar { tagGetChar :: Char }
363

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

    
369
instance Arbitrary TagChar where
370
  arbitrary = do
371
    c <- elements tagChar
372
    return (TagChar c)
373

    
374
-- | Generates a tag
375
genTag :: Gen [TagChar]
376
genTag = do
377
  -- the correct value would be C.maxTagLen, but that's way too
378
  -- verbose in unittests, and at the moment I don't see any possible
379
  -- bugs with longer tags and the way we use tags in htools
380
  n <- choose (1, 10)
381
  vector n
382

    
383
-- | Generates a list of tags (correctly upper bounded).
384
genTags :: Gen [String]
385
genTags = do
386
  -- the correct value would be C.maxTagsPerObj, but per the comment
387
  -- in genTag, we don't use tags enough in htools to warrant testing
388
  -- such big values
389
  n <- choose (0, 10::Int)
390
  tags <- mapM (const genTag) [1..n]
391
  return $ map (map tagGetChar) tags
392

    
393
instance Arbitrary Types.InstanceStatus where
394
    arbitrary = elements [minBound..maxBound]
395

    
396
-- | Generates a random instance with maximum disk/mem/cpu values.
397
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
398
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
399
  name <- getFQDN
400
  mem <- choose (0, lim_mem)
401
  dsk <- choose (0, lim_dsk)
402
  run_st <- arbitrary
403
  pn <- arbitrary
404
  sn <- arbitrary
405
  vcpus <- choose (0, lim_cpu)
406
  dt <- arbitrary
407
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
408

    
409
-- | Generates an instance smaller than a node.
410
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
411
genInstanceSmallerThanNode node =
412
  genInstanceSmallerThan (Node.availMem node `div` 2)
413
                         (Node.availDisk node `div` 2)
414
                         (Node.availCpu node `div` 2)
415

    
416
-- let's generate a random instance
417
instance Arbitrary Instance.Instance where
418
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
419

    
420
-- | Generas an arbitrary node based on sizing information.
421
genNode :: Maybe Int -- ^ Minimum node size in terms of units
422
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
423
                     -- just by the max... constants)
424
        -> Gen Node.Node
425
genNode min_multiplier max_multiplier = do
426
  let (base_mem, base_dsk, base_cpu) =
427
        case min_multiplier of
428
          Just mm -> (mm * Types.unitMem,
429
                      mm * Types.unitDsk,
430
                      mm * Types.unitCpu)
431
          Nothing -> (0, 0, 0)
432
      (top_mem, top_dsk, top_cpu)  =
433
        case max_multiplier of
434
          Just mm -> (mm * Types.unitMem,
435
                      mm * Types.unitDsk,
436
                      mm * Types.unitCpu)
437
          Nothing -> (maxMem, maxDsk, maxCpu)
438
  name  <- getFQDN
439
  mem_t <- choose (base_mem, top_mem)
440
  mem_f <- choose (base_mem, mem_t)
441
  mem_n <- choose (0, mem_t - mem_f)
442
  dsk_t <- choose (base_dsk, top_dsk)
443
  dsk_f <- choose (base_dsk, dsk_t)
444
  cpu_t <- choose (base_cpu, top_cpu)
445
  offl  <- arbitrary
446
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
447
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
448
      n' = Node.setPolicy nullIPolicy n
449
  return $ Node.buildPeers n' Container.empty
450

    
451
-- | Helper function to generate a sane node.
452
genOnlineNode :: Gen Node.Node
453
genOnlineNode = do
454
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
455
                              not (Node.failN1 n) &&
456
                              Node.availDisk n > 0 &&
457
                              Node.availMem n > 0 &&
458
                              Node.availCpu n > 0)
459

    
460
-- and a random node
461
instance Arbitrary Node.Node where
462
  arbitrary = genNode Nothing Nothing
463

    
464
-- replace disks
465
instance Arbitrary OpCodes.ReplaceDisksMode where
466
  arbitrary = elements [minBound..maxBound]
467

    
468
instance Arbitrary OpCodes.DiskIndex where
469
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
470

    
471
instance Arbitrary OpCodes.OpCode where
472
  arbitrary = do
473
    op_id <- elements OpCodes.allOpIDs
474
    case op_id of
475
      "OP_TEST_DELAY" ->
476
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
477
                 <*> resize maxNodes (listOf getFQDN)
478
      "OP_INSTANCE_REPLACE_DISKS" ->
479
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
480
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
481
      "OP_INSTANCE_FAILOVER" ->
482
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
483
          getMaybe getFQDN
484
      "OP_INSTANCE_MIGRATE" ->
485
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
486
          arbitrary <*> arbitrary <*> getMaybe getFQDN
487
      _ -> fail "Wrong opcode"
488

    
489
instance Arbitrary Jobs.OpStatus where
490
  arbitrary = elements [minBound..maxBound]
491

    
492
instance Arbitrary Jobs.JobStatus where
493
  arbitrary = elements [minBound..maxBound]
494

    
495
newtype SmallRatio = SmallRatio Double deriving Show
496
instance Arbitrary SmallRatio where
497
  arbitrary = do
498
    v <- choose (0, 1)
499
    return $ SmallRatio v
500

    
501
instance Arbitrary Types.AllocPolicy where
502
  arbitrary = elements [minBound..maxBound]
503

    
504
instance Arbitrary Types.DiskTemplate where
505
  arbitrary = elements [minBound..maxBound]
506

    
507
instance Arbitrary Types.FailMode where
508
  arbitrary = elements [minBound..maxBound]
509

    
510
instance Arbitrary Types.EvacMode where
511
  arbitrary = elements [minBound..maxBound]
512

    
513
instance Arbitrary a => Arbitrary (Types.OpResult a) where
514
  arbitrary = arbitrary >>= \c ->
515
              if c
516
                then Types.OpGood <$> arbitrary
517
                else Types.OpFail <$> arbitrary
518

    
519
instance Arbitrary Types.ISpec where
520
  arbitrary = do
521
    mem_s <- arbitrary::Gen (NonNegative Int)
522
    dsk_c <- arbitrary::Gen (NonNegative Int)
523
    dsk_s <- arbitrary::Gen (NonNegative Int)
524
    cpu_c <- arbitrary::Gen (NonNegative Int)
525
    nic_c <- arbitrary::Gen (NonNegative Int)
526
    su    <- arbitrary::Gen (NonNegative Int)
527
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
528
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
529
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
530
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
531
                       , Types.iSpecNicCount   = fromIntegral nic_c
532
                       , Types.iSpecSpindleUse = fromIntegral su
533
                       }
534

    
535
-- | Generates an ispec bigger than the given one.
536
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
537
genBiggerISpec imin = do
538
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
539
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
540
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
541
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
542
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
543
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
544
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
545
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
546
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
547
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
548
                     , Types.iSpecNicCount   = fromIntegral nic_c
549
                     , Types.iSpecSpindleUse = fromIntegral su
550
                     }
551

    
552
instance Arbitrary Types.IPolicy where
553
  arbitrary = do
554
    imin <- arbitrary
555
    istd <- genBiggerISpec imin
556
    imax <- genBiggerISpec istd
557
    num_tmpl <- choose (0, length allDiskTemplates)
558
    dts  <- genUniquesList num_tmpl
559
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
560
    spindle_ratio <- choose (1.0, maxSpindleRatio)
561
    return Types.IPolicy { Types.iPolicyMinSpec = imin
562
                         , Types.iPolicyStdSpec = istd
563
                         , Types.iPolicyMaxSpec = imax
564
                         , Types.iPolicyDiskTemplates = dts
565
                         , Types.iPolicyVcpuRatio = vcpu_ratio
566
                         , Types.iPolicySpindleRatio = spindle_ratio
567
                         }
568

    
569
instance Arbitrary Objects.Hypervisor where
570
  arbitrary = elements [minBound..maxBound]
571

    
572
instance Arbitrary Objects.PartialNDParams where
573
  arbitrary = Objects.PartialNDParams <$> arbitrary <*> arbitrary
574

    
575
instance Arbitrary Objects.Node where
576
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
577
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
578
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
579
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
580
              <*> (Set.fromList <$> genTags)
581

    
582
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
583
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
584

    
585
instance Arbitrary Rpc.RpcCallInstanceList where
586
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
587

    
588
instance Arbitrary Rpc.RpcCallNodeInfo where
589
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
590

    
591
-- | Custom 'Qlang.Filter' generator (top-level), which enforces a
592
-- (sane) limit on the depth of the generated filters.
593
genFilter :: Gen (Qlang.Filter Qlang.FilterField)
594
genFilter = choose (0, 10) >>= genFilter'
595

    
596
-- | Custom generator for filters that correctly halves the state of
597
-- the generators at each recursive step, per the QuickCheck
598
-- documentation, in order not to run out of memory.
599
genFilter' :: Int -> Gen (Qlang.Filter Qlang.FilterField)
600
genFilter' 0 =
601
  oneof [ return Qlang.EmptyFilter
602
        , Qlang.TrueFilter     <$> getName
603
        , Qlang.EQFilter       <$> getName <*> value
604
        , Qlang.LTFilter       <$> getName <*> value
605
        , Qlang.GTFilter       <$> getName <*> value
606
        , Qlang.LEFilter       <$> getName <*> value
607
        , Qlang.GEFilter       <$> getName <*> value
608
        , Qlang.RegexpFilter   <$> getName <*> getName
609
        , Qlang.ContainsFilter <$> getName <*> value
610
        ]
611
    where value = oneof [ Qlang.QuotedString <$> getName
612
                        , Qlang.NumericValue <$> arbitrary
613
                        ]
614
genFilter' n = do
615
  oneof [ Qlang.AndFilter  <$> vectorOf n'' (genFilter' n')
616
        , Qlang.OrFilter   <$> vectorOf n'' (genFilter' n')
617
        , Qlang.NotFilter  <$> genFilter' n'
618
        ]
619
  where n' = n `div` 2 -- sub-filter generator size
620
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
621
                       -- so use this for and/or filter list length
622

    
623
instance Arbitrary Qlang.ItemType where
624
  arbitrary = elements [minBound..maxBound]
625

    
626
-- * Actual tests
627

    
628
-- ** Utils tests
629

    
630
-- | Helper to generate a small string that doesn't contain commas.
631
genNonCommaString :: Gen [Char]
632
genNonCommaString = do
633
  size <- choose (0, 20) -- arbitrary max size
634
  vectorOf size (arbitrary `suchThat` ((/=) ','))
635

    
636
-- | If the list is not just an empty element, and if the elements do
637
-- not contain commas, then join+split should be idempotent.
638
prop_Utils_commaJoinSplit :: Property
639
prop_Utils_commaJoinSplit =
640
  forAll (choose (0, 20)) $ \llen ->
641
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
642
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
643

    
644
-- | Split and join should always be idempotent.
645
prop_Utils_commaSplitJoin :: [Char] -> Property
646
prop_Utils_commaSplitJoin s =
647
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
648

    
649
-- | fromObjWithDefault, we test using the Maybe monad and an integer
650
-- value.
651
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
652
prop_Utils_fromObjWithDefault def_value random_key =
653
  -- a missing key will be returned with the default
654
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
655
  -- a found key will be returned as is, not with default
656
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
657
       random_key (def_value+1) == Just def_value
658

    
659
-- | Test that functional if' behaves like the syntactic sugar if.
660
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
661
prop_Utils_if'if cnd a b =
662
  Utils.if' cnd a b ==? if cnd then a else b
663

    
664
-- | Test basic select functionality
665
prop_Utils_select :: Int      -- ^ Default result
666
                  -> [Int]    -- ^ List of False values
667
                  -> [Int]    -- ^ List of True values
668
                  -> Gen Prop -- ^ Test result
669
prop_Utils_select def lst1 lst2 =
670
  Utils.select def (flist ++ tlist) ==? expectedresult
671
    where expectedresult = Utils.if' (null lst2) def (head lst2)
672
          flist = zip (repeat False) lst1
673
          tlist = zip (repeat True)  lst2
674

    
675
-- | Test basic select functionality with undefined default
676
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
677
                         -> NonEmptyList Int -- ^ List of True values
678
                         -> Gen Prop         -- ^ Test result
679
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
680
  Utils.select undefined (flist ++ tlist) ==? head lst2
681
    where flist = zip (repeat False) lst1
682
          tlist = zip (repeat True)  lst2
683

    
684
-- | Test basic select functionality with undefined list values
685
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
686
                         -> NonEmptyList Int -- ^ List of True values
687
                         -> Gen Prop         -- ^ Test result
688
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
689
  Utils.select undefined cndlist ==? head lst2
690
    where flist = zip (repeat False) lst1
691
          tlist = zip (repeat True)  lst2
692
          cndlist = flist ++ tlist ++ [undefined]
693

    
694
prop_Utils_parseUnit :: NonNegative Int -> Property
695
prop_Utils_parseUnit (NonNegative n) =
696
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
697
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
698
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
699
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
700
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
701
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
702
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
703
  printTestCase "Internal error/overflow?"
704
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
705
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
706
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
707
        n_gb = n_mb * 1000
708
        n_tb = n_gb * 1000
709

    
710
-- | Test list for the Utils module.
711
testSuite "Utils"
712
            [ 'prop_Utils_commaJoinSplit
713
            , 'prop_Utils_commaSplitJoin
714
            , 'prop_Utils_fromObjWithDefault
715
            , 'prop_Utils_if'if
716
            , 'prop_Utils_select
717
            , 'prop_Utils_select_undefd
718
            , 'prop_Utils_select_undefv
719
            , 'prop_Utils_parseUnit
720
            ]
721

    
722
-- ** PeerMap tests
723

    
724
-- | Make sure add is idempotent.
725
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
726
                           -> PeerMap.Key -> PeerMap.Elem -> Property
727
prop_PeerMap_addIdempotent pmap key em =
728
  fn puniq ==? fn (fn puniq)
729
    where fn = PeerMap.add key em
730
          puniq = PeerMap.accumArray const pmap
731

    
732
-- | Make sure remove is idempotent.
733
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
734
prop_PeerMap_removeIdempotent pmap key =
735
  fn puniq ==? fn (fn puniq)
736
    where fn = PeerMap.remove key
737
          puniq = PeerMap.accumArray const pmap
738

    
739
-- | Make sure a missing item returns 0.
740
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
741
prop_PeerMap_findMissing pmap key =
742
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
743
    where puniq = PeerMap.accumArray const pmap
744

    
745
-- | Make sure an added item is found.
746
prop_PeerMap_addFind :: PeerMap.PeerMap
747
                     -> PeerMap.Key -> PeerMap.Elem -> Property
748
prop_PeerMap_addFind pmap key em =
749
  PeerMap.find key (PeerMap.add key em puniq) ==? em
750
    where puniq = PeerMap.accumArray const pmap
751

    
752
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
753
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
754
prop_PeerMap_maxElem pmap =
755
  PeerMap.maxElem puniq ==? if null puniq then 0
756
                              else (maximum . snd . unzip) puniq
757
    where puniq = PeerMap.accumArray const pmap
758

    
759
-- | List of tests for the PeerMap module.
760
testSuite "PeerMap"
761
            [ 'prop_PeerMap_addIdempotent
762
            , 'prop_PeerMap_removeIdempotent
763
            , 'prop_PeerMap_maxElem
764
            , 'prop_PeerMap_addFind
765
            , 'prop_PeerMap_findMissing
766
            ]
767

    
768
-- ** Container tests
769

    
770
-- we silence the following due to hlint bug fixed in later versions
771
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
772
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
773
prop_Container_addTwo cdata i1 i2 =
774
  fn i1 i2 cont == fn i2 i1 cont &&
775
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
776
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
777
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
778

    
779
prop_Container_nameOf :: Node.Node -> Property
780
prop_Container_nameOf node =
781
  let nl = makeSmallCluster node 1
782
      fnode = head (Container.elems nl)
783
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
784

    
785
-- | We test that in a cluster, given a random node, we can find it by
786
-- its name and alias, as long as all names and aliases are unique,
787
-- and that we fail to find a non-existing name.
788
prop_Container_findByName :: Property
789
prop_Container_findByName =
790
  forAll (genNode (Just 1) Nothing) $ \node ->
791
  forAll (choose (1, 20)) $ \ cnt ->
792
  forAll (choose (0, cnt - 1)) $ \ fidx ->
793
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
794
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
795
  let names = zip (take cnt allnames) (drop cnt allnames)
796
      nl = makeSmallCluster node cnt
797
      nodes = Container.elems nl
798
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
799
                                             nn { Node.name = name,
800
                                                  Node.alias = alias }))
801
               $ zip names nodes
802
      nl' = Container.fromList nodes'
803
      target = snd (nodes' !! fidx)
804
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
805
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
806
     printTestCase "Found non-existing name"
807
       (isNothing (Container.findByName nl' othername))
808

    
809
testSuite "Container"
810
            [ 'prop_Container_addTwo
811
            , 'prop_Container_nameOf
812
            , 'prop_Container_findByName
813
            ]
814

    
815
-- ** Instance tests
816

    
817
-- Simple instance tests, we only have setter/getters
818

    
819
prop_Instance_creat :: Instance.Instance -> Property
820
prop_Instance_creat inst =
821
  Instance.name inst ==? Instance.alias inst
822

    
823
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
824
prop_Instance_setIdx inst idx =
825
  Instance.idx (Instance.setIdx inst idx) ==? idx
826

    
827
prop_Instance_setName :: Instance.Instance -> String -> Bool
828
prop_Instance_setName inst name =
829
  Instance.name newinst == name &&
830
  Instance.alias newinst == name
831
    where newinst = Instance.setName inst name
832

    
833
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
834
prop_Instance_setAlias inst name =
835
  Instance.name newinst == Instance.name inst &&
836
  Instance.alias newinst == name
837
    where newinst = Instance.setAlias inst name
838

    
839
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
840
prop_Instance_setPri inst pdx =
841
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
842

    
843
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
844
prop_Instance_setSec inst sdx =
845
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
846

    
847
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
848
prop_Instance_setBoth inst pdx sdx =
849
  Instance.pNode si == pdx && Instance.sNode si == sdx
850
    where si = Instance.setBoth inst pdx sdx
851

    
852
prop_Instance_shrinkMG :: Instance.Instance -> Property
853
prop_Instance_shrinkMG inst =
854
  Instance.mem inst >= 2 * Types.unitMem ==>
855
    case Instance.shrinkByType inst Types.FailMem of
856
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
857
      _ -> False
858

    
859
prop_Instance_shrinkMF :: Instance.Instance -> Property
860
prop_Instance_shrinkMF inst =
861
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
862
    let inst' = inst { Instance.mem = mem}
863
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
864

    
865
prop_Instance_shrinkCG :: Instance.Instance -> Property
866
prop_Instance_shrinkCG inst =
867
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
868
    case Instance.shrinkByType inst Types.FailCPU of
869
      Types.Ok inst' ->
870
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
871
      _ -> False
872

    
873
prop_Instance_shrinkCF :: Instance.Instance -> Property
874
prop_Instance_shrinkCF inst =
875
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
876
    let inst' = inst { Instance.vcpus = vcpus }
877
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
878

    
879
prop_Instance_shrinkDG :: Instance.Instance -> Property
880
prop_Instance_shrinkDG inst =
881
  Instance.dsk inst >= 2 * Types.unitDsk ==>
882
    case Instance.shrinkByType inst Types.FailDisk of
883
      Types.Ok inst' ->
884
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
885
      _ -> False
886

    
887
prop_Instance_shrinkDF :: Instance.Instance -> Property
888
prop_Instance_shrinkDF inst =
889
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
890
    let inst' = inst { Instance.dsk = dsk }
891
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
892

    
893
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
894
prop_Instance_setMovable inst m =
895
  Instance.movable inst' ==? m
896
    where inst' = Instance.setMovable inst m
897

    
898
testSuite "Instance"
899
            [ 'prop_Instance_creat
900
            , 'prop_Instance_setIdx
901
            , 'prop_Instance_setName
902
            , 'prop_Instance_setAlias
903
            , 'prop_Instance_setPri
904
            , 'prop_Instance_setSec
905
            , 'prop_Instance_setBoth
906
            , 'prop_Instance_shrinkMG
907
            , 'prop_Instance_shrinkMF
908
            , 'prop_Instance_shrinkCG
909
            , 'prop_Instance_shrinkCF
910
            , 'prop_Instance_shrinkDG
911
            , 'prop_Instance_shrinkDF
912
            , 'prop_Instance_setMovable
913
            ]
914

    
915
-- ** Backends
916

    
917
-- *** Text backend tests
918

    
919
-- Instance text loader tests
920

    
921
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
922
                        -> NonEmptyList Char -> [Char]
923
                        -> NonNegative Int -> NonNegative Int -> Bool
924
                        -> Types.DiskTemplate -> Int -> Property
925
prop_Text_Load_Instance name mem dsk vcpus status
926
                        (NonEmpty pnode) snode
927
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
928
  pnode /= snode && pdx /= sdx ==>
929
  let vcpus_s = show vcpus
930
      dsk_s = show dsk
931
      mem_s = show mem
932
      su_s = show su
933
      status_s = Types.instanceStatusToRaw status
934
      ndx = if null snode
935
              then [(pnode, pdx)]
936
              else [(pnode, pdx), (snode, sdx)]
937
      nl = Map.fromList ndx
938
      tags = ""
939
      sbal = if autobal then "Y" else "N"
940
      sdt = Types.diskTemplateToRaw dt
941
      inst = Text.loadInst nl
942
             [name, mem_s, dsk_s, vcpus_s, status_s,
943
              sbal, pnode, snode, sdt, tags, su_s]
944
      fail1 = Text.loadInst nl
945
              [name, mem_s, dsk_s, vcpus_s, status_s,
946
               sbal, pnode, pnode, tags]
947
  in case inst of
948
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
949
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
950
                                        \ loading the instance" $
951
               Instance.name i == name &&
952
               Instance.vcpus i == vcpus &&
953
               Instance.mem i == mem &&
954
               Instance.pNode i == pdx &&
955
               Instance.sNode i == (if null snode
956
                                      then Node.noSecondary
957
                                      else sdx) &&
958
               Instance.autoBalance i == autobal &&
959
               Instance.spindleUse i == su &&
960
               Types.isBad fail1
961

    
962
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
963
prop_Text_Load_InstanceFail ktn fields =
964
  length fields /= 10 && length fields /= 11 ==>
965
    case Text.loadInst nl fields of
966
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
967
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
968
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
969
    where nl = Map.fromList ktn
970

    
971
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
972
                    -> Int -> Bool -> Bool
973
prop_Text_Load_Node name tm nm fm td fd tc fo =
974
  let conv v = if v < 0
975
                 then "?"
976
                 else show v
977
      tm_s = conv tm
978
      nm_s = conv nm
979
      fm_s = conv fm
980
      td_s = conv td
981
      fd_s = conv fd
982
      tc_s = conv tc
983
      fo_s = if fo
984
               then "Y"
985
               else "N"
986
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
987
      gid = Group.uuid defGroup
988
  in case Text.loadNode defGroupAssoc
989
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
990
       Nothing -> False
991
       Just (name', node) ->
992
         if fo || any_broken
993
           then Node.offline node
994
           else Node.name node == name' && name' == name &&
995
                Node.alias node == name &&
996
                Node.tMem node == fromIntegral tm &&
997
                Node.nMem node == nm &&
998
                Node.fMem node == fm &&
999
                Node.tDsk node == fromIntegral td &&
1000
                Node.fDsk node == fd &&
1001
                Node.tCpu node == fromIntegral tc
1002

    
1003
prop_Text_Load_NodeFail :: [String] -> Property
1004
prop_Text_Load_NodeFail fields =
1005
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
1006

    
1007
prop_Text_NodeLSIdempotent :: Property
1008
prop_Text_NodeLSIdempotent =
1009
  forAll (genNode (Just 1) Nothing) $ \node ->
1010
  -- override failN1 to what loadNode returns by default
1011
  let n = Node.setPolicy Types.defIPolicy $
1012
          node { Node.failN1 = True, Node.offline = False }
1013
  in
1014
    (Text.loadNode defGroupAssoc.
1015
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
1016
    Just (Node.name n, n)
1017

    
1018
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
1019
prop_Text_ISpecIdempotent ispec =
1020
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
1021
       Text.serializeISpec $ ispec of
1022
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
1023
    Types.Ok ispec' -> ispec ==? ispec'
1024

    
1025
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
1026
prop_Text_IPolicyIdempotent ipol =
1027
  case Text.loadIPolicy . Utils.sepSplit '|' $
1028
       Text.serializeIPolicy owner ipol of
1029
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
1030
    Types.Ok res -> (owner, ipol) ==? res
1031
  where owner = "dummy"
1032

    
1033
-- | This property, while being in the text tests, does more than just
1034
-- test end-to-end the serialisation and loading back workflow; it
1035
-- also tests the Loader.mergeData and the actuall
1036
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
1037
-- allocations, not for the business logic). As such, it's a quite
1038
-- complex and slow test, and that's the reason we restrict it to
1039
-- small cluster sizes.
1040
prop_Text_CreateSerialise :: Property
1041
prop_Text_CreateSerialise =
1042
  forAll genTags $ \ctags ->
1043
  forAll (choose (1, 20)) $ \maxiter ->
1044
  forAll (choose (2, 10)) $ \count ->
1045
  forAll genOnlineNode $ \node ->
1046
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1047
  let nl = makeSmallCluster node count
1048
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1049
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
1050
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
1051
     of
1052
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1053
       Types.Ok (_, _, _, [], _) -> printTestCase
1054
                                    "Failed to allocate: no allocations" False
1055
       Types.Ok (_, nl', il', _, _) ->
1056
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
1057
                     Types.defIPolicy
1058
             saved = Text.serializeCluster cdata
1059
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
1060
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
1061
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
1062
                ctags ==? ctags2 .&&.
1063
                Types.defIPolicy ==? cpol2 .&&.
1064
                il' ==? il2 .&&.
1065
                defGroupList ==? gl2 .&&.
1066
                nl' ==? nl2
1067

    
1068
testSuite "Text"
1069
            [ 'prop_Text_Load_Instance
1070
            , 'prop_Text_Load_InstanceFail
1071
            , 'prop_Text_Load_Node
1072
            , 'prop_Text_Load_NodeFail
1073
            , 'prop_Text_NodeLSIdempotent
1074
            , 'prop_Text_ISpecIdempotent
1075
            , 'prop_Text_IPolicyIdempotent
1076
            , 'prop_Text_CreateSerialise
1077
            ]
1078

    
1079
-- *** Simu backend
1080

    
1081
-- | Generates a tuple of specs for simulation.
1082
genSimuSpec :: Gen (String, Int, Int, Int, Int)
1083
genSimuSpec = do
1084
  pol <- elements [C.allocPolicyPreferred,
1085
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
1086
                  "p", "a", "u"]
1087
 -- should be reasonable (nodes/group), bigger values only complicate
1088
 -- the display of failed tests, and we don't care (in this particular
1089
 -- test) about big node groups
1090
  nodes <- choose (0, 20)
1091
  dsk <- choose (0, maxDsk)
1092
  mem <- choose (0, maxMem)
1093
  cpu <- choose (0, maxCpu)
1094
  return (pol, nodes, dsk, mem, cpu)
1095

    
1096
-- | Checks that given a set of corrects specs, we can load them
1097
-- successfully, and that at high-level the values look right.
1098
prop_Simu_Load :: Property
1099
prop_Simu_Load =
1100
  forAll (choose (0, 10)) $ \ngroups ->
1101
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
1102
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
1103
                                          p n d m c::String) specs
1104
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
1105
      mdc_in = concatMap (\(_, n, d, m, c) ->
1106
                            replicate n (fromIntegral m, fromIntegral d,
1107
                                         fromIntegral c,
1108
                                         fromIntegral m, fromIntegral d))
1109
               specs :: [(Double, Double, Double, Int, Int)]
1110
  in case Simu.parseData strspecs of
1111
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1112
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1113
         let nodes = map snd $ IntMap.toAscList nl
1114
             nidx = map Node.idx nodes
1115
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1116
                                   Node.fMem n, Node.fDsk n)) nodes
1117
         in
1118
         Container.size gl ==? ngroups .&&.
1119
         Container.size nl ==? totnodes .&&.
1120
         Container.size il ==? 0 .&&.
1121
         length tags ==? 0 .&&.
1122
         ipol ==? Types.defIPolicy .&&.
1123
         nidx ==? [1..totnodes] .&&.
1124
         mdc_in ==? mdc_out .&&.
1125
         map Group.iPolicy (Container.elems gl) ==?
1126
             replicate ngroups Types.defIPolicy
1127

    
1128
testSuite "Simu"
1129
            [ 'prop_Simu_Load
1130
            ]
1131

    
1132
-- ** Node tests
1133

    
1134
prop_Node_setAlias :: Node.Node -> String -> Bool
1135
prop_Node_setAlias node name =
1136
  Node.name newnode == Node.name node &&
1137
  Node.alias newnode == name
1138
    where newnode = Node.setAlias node name
1139

    
1140
prop_Node_setOffline :: Node.Node -> Bool -> Property
1141
prop_Node_setOffline node status =
1142
  Node.offline newnode ==? status
1143
    where newnode = Node.setOffline node status
1144

    
1145
prop_Node_setXmem :: Node.Node -> Int -> Property
1146
prop_Node_setXmem node xm =
1147
  Node.xMem newnode ==? xm
1148
    where newnode = Node.setXmem node xm
1149

    
1150
prop_Node_setMcpu :: Node.Node -> Double -> Property
1151
prop_Node_setMcpu node mc =
1152
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1153
    where newnode = Node.setMcpu node mc
1154

    
1155
-- | Check that an instance add with too high memory or disk will be
1156
-- rejected.
1157
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1158
prop_Node_addPriFM node inst =
1159
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1160
  not (Instance.isOffline inst) ==>
1161
  case Node.addPri node inst'' of
1162
    Types.OpFail Types.FailMem -> True
1163
    _ -> False
1164
  where inst' = setInstanceSmallerThanNode node inst
1165
        inst'' = inst' { Instance.mem = Instance.mem inst }
1166

    
1167
-- | Check that adding a primary instance with too much disk fails
1168
-- with type FailDisk.
1169
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1170
prop_Node_addPriFD node inst =
1171
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1172
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1173
  let inst' = setInstanceSmallerThanNode node inst
1174
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1175
                     , Instance.diskTemplate = dt }
1176
  in case Node.addPri node inst'' of
1177
       Types.OpFail Types.FailDisk -> True
1178
       _ -> False
1179

    
1180
-- | Check that adding a primary instance with too many VCPUs fails
1181
-- with type FailCPU.
1182
prop_Node_addPriFC :: Property
1183
prop_Node_addPriFC =
1184
  forAll (choose (1, maxCpu)) $ \extra ->
1185
  forAll genOnlineNode $ \node ->
1186
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1187
  let inst' = setInstanceSmallerThanNode node inst
1188
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1189
  in case Node.addPri node inst'' of
1190
       Types.OpFail Types.FailCPU -> property True
1191
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1192

    
1193
-- | Check that an instance add with too high memory or disk will be
1194
-- rejected.
1195
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1196
prop_Node_addSec node inst pdx =
1197
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1198
    not (Instance.isOffline inst)) ||
1199
   Instance.dsk inst >= Node.fDsk node) &&
1200
  not (Node.failN1 node) ==>
1201
      isFailure (Node.addSec node inst pdx)
1202

    
1203
-- | Check that an offline instance with reasonable disk size but
1204
-- extra mem/cpu can always be added.
1205
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1206
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1207
  forAll genOnlineNode $ \node ->
1208
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1209
  let inst' = inst { Instance.runSt = Types.AdminOffline
1210
                   , Instance.mem = Node.availMem node + extra_mem
1211
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1212
  in case Node.addPri node inst' of
1213
       Types.OpGood _ -> property True
1214
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1215

    
1216
-- | Check that an offline instance with reasonable disk size but
1217
-- extra mem/cpu can always be added.
1218
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1219
                        -> Types.Ndx -> Property
1220
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1221
  forAll genOnlineNode $ \node ->
1222
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1223
  let inst' = inst { Instance.runSt = Types.AdminOffline
1224
                   , Instance.mem = Node.availMem node + extra_mem
1225
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1226
                   , Instance.diskTemplate = Types.DTDrbd8 }
1227
  in case Node.addSec node inst' pdx of
1228
       Types.OpGood _ -> property True
1229
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1230

    
1231
-- | Checks for memory reservation changes.
1232
prop_Node_rMem :: Instance.Instance -> Property
1233
prop_Node_rMem inst =
1234
  not (Instance.isOffline inst) ==>
1235
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1236
  -- ab = auto_balance, nb = non-auto_balance
1237
  -- we use -1 as the primary node of the instance
1238
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1239
                   , Instance.diskTemplate = Types.DTDrbd8 }
1240
      inst_ab = setInstanceSmallerThanNode node inst'
1241
      inst_nb = inst_ab { Instance.autoBalance = False }
1242
      -- now we have the two instances, identical except the
1243
      -- autoBalance attribute
1244
      orig_rmem = Node.rMem node
1245
      inst_idx = Instance.idx inst_ab
1246
      node_add_ab = Node.addSec node inst_ab (-1)
1247
      node_add_nb = Node.addSec node inst_nb (-1)
1248
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1249
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1250
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1251
       (Types.OpGood a_ab, Types.OpGood a_nb,
1252
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1253
         printTestCase "Consistency checks failed" $
1254
           Node.rMem a_ab >  orig_rmem &&
1255
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1256
           Node.rMem a_nb == orig_rmem &&
1257
           Node.rMem d_ab == orig_rmem &&
1258
           Node.rMem d_nb == orig_rmem &&
1259
           -- this is not related to rMem, but as good a place to
1260
           -- test as any
1261
           inst_idx `elem` Node.sList a_ab &&
1262
           inst_idx `notElem` Node.sList d_ab
1263
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1264

    
1265
-- | Check mdsk setting.
1266
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1267
prop_Node_setMdsk node mx =
1268
  Node.loDsk node' >= 0 &&
1269
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1270
  Node.availDisk node' >= 0 &&
1271
  Node.availDisk node' <= Node.fDsk node' &&
1272
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1273
  Node.mDsk node' == mx'
1274
    where node' = Node.setMdsk node mx'
1275
          SmallRatio mx' = mx
1276

    
1277
-- Check tag maps
1278
prop_Node_tagMaps_idempotent :: Property
1279
prop_Node_tagMaps_idempotent =
1280
  forAll genTags $ \tags ->
1281
  Node.delTags (Node.addTags m tags) tags ==? m
1282
    where m = Map.empty
1283

    
1284
prop_Node_tagMaps_reject :: Property
1285
prop_Node_tagMaps_reject =
1286
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1287
  let m = Node.addTags Map.empty tags
1288
  in all (\t -> Node.rejectAddTags m [t]) tags
1289

    
1290
prop_Node_showField :: Node.Node -> Property
1291
prop_Node_showField node =
1292
  forAll (elements Node.defaultFields) $ \ field ->
1293
  fst (Node.showHeader field) /= Types.unknownField &&
1294
  Node.showField node field /= Types.unknownField
1295

    
1296
prop_Node_computeGroups :: [Node.Node] -> Bool
1297
prop_Node_computeGroups nodes =
1298
  let ng = Node.computeGroups nodes
1299
      onlyuuid = map fst ng
1300
  in length nodes == sum (map (length . snd) ng) &&
1301
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1302
     length (nub onlyuuid) == length onlyuuid &&
1303
     (null nodes || not (null ng))
1304

    
1305
-- Check idempotence of add/remove operations
1306
prop_Node_addPri_idempotent :: Property
1307
prop_Node_addPri_idempotent =
1308
  forAll genOnlineNode $ \node ->
1309
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1310
  case Node.addPri node inst of
1311
    Types.OpGood node' -> Node.removePri node' inst ==? node
1312
    _ -> failTest "Can't add instance"
1313

    
1314
prop_Node_addSec_idempotent :: Property
1315
prop_Node_addSec_idempotent =
1316
  forAll genOnlineNode $ \node ->
1317
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1318
  let pdx = Node.idx node + 1
1319
      inst' = Instance.setPri inst pdx
1320
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1321
  in case Node.addSec node inst'' pdx of
1322
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1323
       _ -> failTest "Can't add instance"
1324

    
1325
testSuite "Node"
1326
            [ 'prop_Node_setAlias
1327
            , 'prop_Node_setOffline
1328
            , 'prop_Node_setMcpu
1329
            , 'prop_Node_setXmem
1330
            , 'prop_Node_addPriFM
1331
            , 'prop_Node_addPriFD
1332
            , 'prop_Node_addPriFC
1333
            , 'prop_Node_addSec
1334
            , 'prop_Node_addOfflinePri
1335
            , 'prop_Node_addOfflineSec
1336
            , 'prop_Node_rMem
1337
            , 'prop_Node_setMdsk
1338
            , 'prop_Node_tagMaps_idempotent
1339
            , 'prop_Node_tagMaps_reject
1340
            , 'prop_Node_showField
1341
            , 'prop_Node_computeGroups
1342
            , 'prop_Node_addPri_idempotent
1343
            , 'prop_Node_addSec_idempotent
1344
            ]
1345

    
1346
-- ** Cluster tests
1347

    
1348
-- | Check that the cluster score is close to zero for a homogeneous
1349
-- cluster.
1350
prop_Cluster_Score_Zero :: Node.Node -> Property
1351
prop_Cluster_Score_Zero node =
1352
  forAll (choose (1, 1024)) $ \count ->
1353
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1354
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1355
  let fn = Node.buildPeers node Container.empty
1356
      nlst = replicate count fn
1357
      score = Cluster.compCVNodes nlst
1358
  -- we can't say == 0 here as the floating point errors accumulate;
1359
  -- this should be much lower than the default score in CLI.hs
1360
  in score <= 1e-12
1361

    
1362
-- | Check that cluster stats are sane.
1363
prop_Cluster_CStats_sane :: Property
1364
prop_Cluster_CStats_sane =
1365
  forAll (choose (1, 1024)) $ \count ->
1366
  forAll genOnlineNode $ \node ->
1367
  let fn = Node.buildPeers node Container.empty
1368
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1369
      nl = Container.fromList nlst
1370
      cstats = Cluster.totalResources nl
1371
  in Cluster.csAdsk cstats >= 0 &&
1372
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1373

    
1374
-- | Check that one instance is allocated correctly, without
1375
-- rebalances needed.
1376
prop_Cluster_Alloc_sane :: Instance.Instance -> Property
1377
prop_Cluster_Alloc_sane inst =
1378
  forAll (choose (5, 20)) $ \count ->
1379
  forAll genOnlineNode $ \node ->
1380
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1381
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1382
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1383
     Cluster.tryAlloc nl il inst' of
1384
       Types.Bad _ -> False
1385
       Types.Ok as ->
1386
         case Cluster.asSolution as of
1387
           Nothing -> False
1388
           Just (xnl, xi, _, cv) ->
1389
             let il' = Container.add (Instance.idx xi) xi il
1390
                 tbl = Cluster.Table xnl il' cv []
1391
             in not (canBalance tbl True True False)
1392

    
1393
-- | Checks that on a 2-5 node cluster, we can allocate a random
1394
-- instance spec via tiered allocation (whatever the original instance
1395
-- spec), on either one or two nodes. Furthermore, we test that
1396
-- computed allocation statistics are correct.
1397
prop_Cluster_CanTieredAlloc :: Instance.Instance -> Property
1398
prop_Cluster_CanTieredAlloc inst =
1399
  forAll (choose (2, 5)) $ \count ->
1400
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1401
  let nl = makeSmallCluster node count
1402
      il = Container.empty
1403
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1404
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1405
  in case allocnodes >>= \allocnodes' ->
1406
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1407
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1408
       Types.Ok (_, nl', il', ixes, cstats) ->
1409
         let (ai_alloc, ai_pool, ai_unav) =
1410
               Cluster.computeAllocationDelta
1411
                (Cluster.totalResources nl)
1412
                (Cluster.totalResources nl')
1413
             all_nodes = Container.elems nl
1414
         in property (not (null ixes)) .&&.
1415
            IntMap.size il' ==? length ixes .&&.
1416
            length ixes ==? length cstats .&&.
1417
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1418
              sum (map Node.hiCpu all_nodes) .&&.
1419
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1420
              sum (map Node.tCpu all_nodes) .&&.
1421
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1422
              truncate (sum (map Node.tMem all_nodes)) .&&.
1423
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1424
              truncate (sum (map Node.tDsk all_nodes))
1425

    
1426
-- | Helper function to create a cluster with the given range of nodes
1427
-- and allocate an instance on it.
1428
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1429
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1430
genClusterAlloc count node inst =
1431
  let nl = makeSmallCluster node count
1432
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1433
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1434
     Cluster.tryAlloc nl Container.empty inst of
1435
       Types.Bad _ -> Types.Bad "Can't allocate"
1436
       Types.Ok as ->
1437
         case Cluster.asSolution as of
1438
           Nothing -> Types.Bad "Empty solution?"
1439
           Just (xnl, xi, _, _) ->
1440
             let xil = Container.add (Instance.idx xi) xi Container.empty
1441
             in Types.Ok (xnl, xil, xi)
1442

    
1443
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1444
-- we can also relocate it.
1445
prop_Cluster_AllocRelocate :: Property
1446
prop_Cluster_AllocRelocate =
1447
  forAll (choose (4, 8)) $ \count ->
1448
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1449
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1450
  case genClusterAlloc count node inst of
1451
    Types.Bad msg -> failTest msg
1452
    Types.Ok (nl, il, inst') ->
1453
      case IAlloc.processRelocate defGroupList nl il
1454
             (Instance.idx inst) 1
1455
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1456
                 then Instance.sNode
1457
                 else Instance.pNode) inst'] of
1458
        Types.Ok _ -> property True
1459
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1460

    
1461
-- | Helper property checker for the result of a nodeEvac or
1462
-- changeGroup operation.
1463
check_EvacMode :: Group.Group -> Instance.Instance
1464
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1465
               -> Property
1466
check_EvacMode grp inst result =
1467
  case result of
1468
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1469
    Types.Ok (_, _, es) ->
1470
      let moved = Cluster.esMoved es
1471
          failed = Cluster.esFailed es
1472
          opcodes = not . null $ Cluster.esOpCodes es
1473
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1474
         failmsg "'opcodes' is null" opcodes .&&.
1475
         case moved of
1476
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1477
                               .&&.
1478
                               failmsg "wrong target group"
1479
                                         (gdx == Group.idx grp)
1480
           v -> failmsg  ("invalid solution: " ++ show v) False
1481
  where failmsg :: String -> Bool -> Property
1482
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1483
        idx = Instance.idx inst
1484

    
1485
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1486
-- we can also node-evacuate it.
1487
prop_Cluster_AllocEvacuate :: Property
1488
prop_Cluster_AllocEvacuate =
1489
  forAll (choose (4, 8)) $ \count ->
1490
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1491
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1492
  case genClusterAlloc count node inst of
1493
    Types.Bad msg -> failTest msg
1494
    Types.Ok (nl, il, inst') ->
1495
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
1496
                              Cluster.tryNodeEvac defGroupList nl il mode
1497
                                [Instance.idx inst']) .
1498
                              evacModeOptions .
1499
                              Instance.mirrorType $ inst'
1500

    
1501
-- | Checks that on a 4-8 node cluster with two node groups, once we
1502
-- allocate an instance on the first node group, we can also change
1503
-- its group.
1504
prop_Cluster_AllocChangeGroup :: Property
1505
prop_Cluster_AllocChangeGroup =
1506
  forAll (choose (4, 8)) $ \count ->
1507
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1508
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1509
  case genClusterAlloc count node inst of
1510
    Types.Bad msg -> failTest msg
1511
    Types.Ok (nl, il, inst') ->
1512
      -- we need to add a second node group and nodes to the cluster
1513
      let nl2 = Container.elems $ makeSmallCluster node count
1514
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1515
          maxndx = maximum . map Node.idx $ nl2
1516
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1517
                             , Node.idx = Node.idx n + maxndx }) nl2
1518
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1519
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1520
          nl' = IntMap.union nl nl4
1521
      in check_EvacMode grp2 inst' $
1522
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1523

    
1524
-- | Check that allocating multiple instances on a cluster, then
1525
-- adding an empty node, results in a valid rebalance.
1526
prop_Cluster_AllocBalance :: Property
1527
prop_Cluster_AllocBalance =
1528
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1529
  forAll (choose (3, 5)) $ \count ->
1530
  not (Node.offline node) && not (Node.failN1 node) ==>
1531
  let nl = makeSmallCluster node count
1532
      (hnode, nl') = IntMap.deleteFindMax nl
1533
      il = Container.empty
1534
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1535
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1536
  in case allocnodes >>= \allocnodes' ->
1537
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1538
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1539
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1540
       Types.Ok (_, xnl, il', _, _) ->
1541
         let ynl = Container.add (Node.idx hnode) hnode xnl
1542
             cv = Cluster.compCV ynl
1543
             tbl = Cluster.Table ynl il' cv []
1544
         in printTestCase "Failed to rebalance" $
1545
            canBalance tbl True True False
1546

    
1547
-- | Checks consistency.
1548
prop_Cluster_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
1549
prop_Cluster_CheckConsistency node inst =
1550
  let nl = makeSmallCluster node 3
1551
      [node1, node2, node3] = Container.elems nl
1552
      node3' = node3 { Node.group = 1 }
1553
      nl' = Container.add (Node.idx node3') node3' nl
1554
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1555
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1556
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1557
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1558
  in null (ccheck [(0, inst1)]) &&
1559
     null (ccheck [(0, inst2)]) &&
1560
     (not . null $ ccheck [(0, inst3)])
1561

    
1562
-- | For now, we only test that we don't lose instances during the split.
1563
prop_Cluster_SplitCluster :: Node.Node -> Instance.Instance -> Property
1564
prop_Cluster_SplitCluster node inst =
1565
  forAll (choose (0, 100)) $ \icnt ->
1566
  let nl = makeSmallCluster node 2
1567
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1568
                   (nl, Container.empty) [1..icnt]
1569
      gni = Cluster.splitCluster nl' il'
1570
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1571
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1572
                                 (Container.elems nl'')) gni
1573

    
1574
-- | Helper function to check if we can allocate an instance on a
1575
-- given node list.
1576
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1577
canAllocOn nl reqnodes inst =
1578
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1579
       Cluster.tryAlloc nl (Container.empty) inst of
1580
       Types.Bad _ -> False
1581
       Types.Ok as ->
1582
         case Cluster.asSolution as of
1583
           Nothing -> False
1584
           Just _ -> True
1585

    
1586
-- | Checks that allocation obeys minimum and maximum instance
1587
-- policies. The unittest generates a random node, duplicates it /count/
1588
-- times, and generates a random instance that can be allocated on
1589
-- this mini-cluster; it then checks that after applying a policy that
1590
-- the instance doesn't fits, the allocation fails.
1591
prop_Cluster_AllocPolicy :: Node.Node -> Property
1592
prop_Cluster_AllocPolicy node =
1593
  -- rqn is the required nodes (1 or 2)
1594
  forAll (choose (1, 2)) $ \rqn ->
1595
  forAll (choose (5, 20)) $ \count ->
1596
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1597
         $ \inst ->
1598
  forAll (arbitrary `suchThat` (isFailure .
1599
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1600
  let node' = Node.setPolicy ipol node
1601
      nl = makeSmallCluster node' count
1602
  in not $ canAllocOn nl rqn inst
1603

    
1604
testSuite "Cluster"
1605
            [ 'prop_Cluster_Score_Zero
1606
            , 'prop_Cluster_CStats_sane
1607
            , 'prop_Cluster_Alloc_sane
1608
            , 'prop_Cluster_CanTieredAlloc
1609
            , 'prop_Cluster_AllocRelocate
1610
            , 'prop_Cluster_AllocEvacuate
1611
            , 'prop_Cluster_AllocChangeGroup
1612
            , 'prop_Cluster_AllocBalance
1613
            , 'prop_Cluster_CheckConsistency
1614
            , 'prop_Cluster_SplitCluster
1615
            , 'prop_Cluster_AllocPolicy
1616
            ]
1617

    
1618
-- ** OpCodes tests
1619

    
1620
-- | Check that opcode serialization is idempotent.
1621
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1622
prop_OpCodes_serialization op =
1623
  case J.readJSON (J.showJSON op) of
1624
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1625
    J.Ok op' -> op ==? op'
1626

    
1627
-- | Check that Python and Haskell defined the same opcode list.
1628
case_OpCodes_AllDefined :: HUnit.Assertion
1629
case_OpCodes_AllDefined = do
1630
  py_stdout <- runPython "from ganeti import opcodes\n\
1631
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
1632
               checkPythonResult
1633
  let py_ops = sort $ lines py_stdout
1634
      hs_ops = OpCodes.allOpIDs
1635
      -- extra_py = py_ops \\ hs_ops
1636
      extra_hs = hs_ops \\ py_ops
1637
  -- FIXME: uncomment when we have parity
1638
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
1639
  --                  unlines extra_py) (null extra_py)
1640
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
1641
                    unlines extra_hs) (null extra_hs)
1642

    
1643
-- | Custom HUnit test case that forks a Python process and checks
1644
-- correspondence between Haskell-generated OpCodes and their Python
1645
-- decoded, validated and re-encoded version.
1646
--
1647
-- Note that we have a strange beast here: since launching Python is
1648
-- expensive, we don't do this via a usual QuickProperty, since that's
1649
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
1650
-- single HUnit assertion, and in it we manually use QuickCheck to
1651
-- generate 500 opcodes times the number of defined opcodes, which
1652
-- then we pass in bulk to Python. The drawbacks to this method are
1653
-- two fold: we cannot control the number of generated opcodes, since
1654
-- HUnit assertions don't get access to the test options, and for the
1655
-- same reason we can't run a repeatable seed. We should probably find
1656
-- a better way to do this, for example by having a
1657
-- separately-launched Python process (if not running the tests would
1658
-- be skipped).
1659
case_OpCodes_py_compat :: HUnit.Assertion
1660
case_OpCodes_py_compat = do
1661
  let num_opcodes = length OpCodes.allOpIDs * 500
1662
  sample_opcodes <- sample' (vectorOf num_opcodes
1663
                             (arbitrary::Gen OpCodes.OpCode))
1664
  let opcodes = head sample_opcodes
1665
      serialized = J.encode opcodes
1666
  py_stdout <-
1667
     runPython "from ganeti import opcodes\n\
1668
               \import sys\n\
1669
               \from ganeti import serializer\n\
1670
               \op_data = serializer.Load(sys.stdin.read())\n\
1671
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
1672
               \for op in decoded:\n\
1673
               \  op.Validate(True)\n\
1674
               \encoded = [op.__getstate__() for op in decoded]\n\
1675
               \print serializer.Dump(encoded)" serialized
1676
     >>= checkPythonResult
1677
  let deserialised = (J.decode py_stdout::J.Result [OpCodes.OpCode])
1678
  decoded <- case deserialised of
1679
               J.Ok ops -> return ops
1680
               J.Error msg ->
1681
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
1682
                 -- this already raised an expection, but we need it
1683
                 -- for proper types
1684
                 >> fail "Unable to decode opcodes"
1685
  HUnit.assertEqual "Mismatch in number of returned opcodes"
1686
    (length opcodes) (length decoded)
1687
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
1688
        ) $ zip opcodes decoded
1689

    
1690
testSuite "OpCodes"
1691
            [ 'prop_OpCodes_serialization
1692
            , 'case_OpCodes_AllDefined
1693
            , 'case_OpCodes_py_compat
1694
            ]
1695

    
1696
-- ** Jobs tests
1697

    
1698
-- | Check that (queued) job\/opcode status serialization is idempotent.
1699
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
1700
prop_Jobs_OpStatus_serialization os =
1701
  case J.readJSON (J.showJSON os) of
1702
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1703
    J.Ok os' -> os ==? os'
1704

    
1705
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
1706
prop_Jobs_JobStatus_serialization js =
1707
  case J.readJSON (J.showJSON js) of
1708
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1709
    J.Ok js' -> js ==? js'
1710

    
1711
testSuite "Jobs"
1712
            [ 'prop_Jobs_OpStatus_serialization
1713
            , 'prop_Jobs_JobStatus_serialization
1714
            ]
1715

    
1716
-- ** Loader tests
1717

    
1718
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1719
prop_Loader_lookupNode ktn inst node =
1720
  Loader.lookupNode nl inst node ==? Map.lookup node nl
1721
    where nl = Map.fromList ktn
1722

    
1723
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1724
prop_Loader_lookupInstance kti inst =
1725
  Loader.lookupInstance il inst ==? Map.lookup inst il
1726
    where il = Map.fromList kti
1727

    
1728
prop_Loader_assignIndices :: Property
1729
prop_Loader_assignIndices =
1730
  -- generate nodes with unique names
1731
  forAll (arbitrary `suchThat`
1732
          (\nodes ->
1733
             let names = map Node.name nodes
1734
             in length names == length (nub names))) $ \nodes ->
1735
  let (nassoc, kt) =
1736
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1737
  in Map.size nassoc == length nodes &&
1738
     Container.size kt == length nodes &&
1739
     if not (null nodes)
1740
       then maximum (IntMap.keys kt) == length nodes - 1
1741
       else True
1742

    
1743
-- | Checks that the number of primary instances recorded on the nodes
1744
-- is zero.
1745
prop_Loader_mergeData :: [Node.Node] -> Bool
1746
prop_Loader_mergeData ns =
1747
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1748
  in case Loader.mergeData [] [] [] []
1749
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1750
    Types.Bad _ -> False
1751
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1752
      let nodes = Container.elems nl
1753
          instances = Container.elems il
1754
      in (sum . map (length . Node.pList)) nodes == 0 &&
1755
         null instances
1756

    
1757
-- | Check that compareNameComponent on equal strings works.
1758
prop_Loader_compareNameComponent_equal :: String -> Bool
1759
prop_Loader_compareNameComponent_equal s =
1760
  BasicTypes.compareNameComponent s s ==
1761
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1762

    
1763
-- | Check that compareNameComponent on prefix strings works.
1764
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1765
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1766
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1767
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1768

    
1769
testSuite "Loader"
1770
            [ 'prop_Loader_lookupNode
1771
            , 'prop_Loader_lookupInstance
1772
            , 'prop_Loader_assignIndices
1773
            , 'prop_Loader_mergeData
1774
            , 'prop_Loader_compareNameComponent_equal
1775
            , 'prop_Loader_compareNameComponent_prefix
1776
            ]
1777

    
1778
-- ** Types tests
1779

    
1780
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1781
prop_Types_AllocPolicy_serialisation apol =
1782
  case J.readJSON (J.showJSON apol) of
1783
    J.Ok p -> p ==? apol
1784
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1785

    
1786
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1787
prop_Types_DiskTemplate_serialisation dt =
1788
  case J.readJSON (J.showJSON dt) of
1789
    J.Ok p -> p ==? dt
1790
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1791

    
1792
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1793
prop_Types_ISpec_serialisation ispec =
1794
  case J.readJSON (J.showJSON ispec) of
1795
    J.Ok p -> p ==? ispec
1796
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1797

    
1798
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1799
prop_Types_IPolicy_serialisation ipol =
1800
  case J.readJSON (J.showJSON ipol) of
1801
    J.Ok p -> p ==? ipol
1802
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1803

    
1804
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1805
prop_Types_EvacMode_serialisation em =
1806
  case J.readJSON (J.showJSON em) of
1807
    J.Ok p -> p ==? em
1808
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1809

    
1810
prop_Types_opToResult :: Types.OpResult Int -> Bool
1811
prop_Types_opToResult op =
1812
  case op of
1813
    Types.OpFail _ -> Types.isBad r
1814
    Types.OpGood v -> case r of
1815
                        Types.Bad _ -> False
1816
                        Types.Ok v' -> v == v'
1817
  where r = Types.opToResult op
1818

    
1819
prop_Types_eitherToResult :: Either String Int -> Bool
1820
prop_Types_eitherToResult ei =
1821
  case ei of
1822
    Left _ -> Types.isBad r
1823
    Right v -> case r of
1824
                 Types.Bad _ -> False
1825
                 Types.Ok v' -> v == v'
1826
    where r = Types.eitherToResult ei
1827

    
1828
testSuite "Types"
1829
            [ 'prop_Types_AllocPolicy_serialisation
1830
            , 'prop_Types_DiskTemplate_serialisation
1831
            , 'prop_Types_ISpec_serialisation
1832
            , 'prop_Types_IPolicy_serialisation
1833
            , 'prop_Types_EvacMode_serialisation
1834
            , 'prop_Types_opToResult
1835
            , 'prop_Types_eitherToResult
1836
            ]
1837

    
1838
-- ** CLI tests
1839

    
1840
-- | Test correct parsing.
1841
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1842
prop_CLI_parseISpec descr dsk mem cpu =
1843
  let str = printf "%d,%d,%d" dsk mem cpu::String
1844
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1845

    
1846
-- | Test parsing failure due to wrong section count.
1847
prop_CLI_parseISpecFail :: String -> Property
1848
prop_CLI_parseISpecFail descr =
1849
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1850
  forAll (replicateM nelems arbitrary) $ \values ->
1851
  let str = intercalate "," $ map show (values::[Int])
1852
  in case CLI.parseISpecString descr str of
1853
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1854
       _ -> property True
1855

    
1856
-- | Test parseYesNo.
1857
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1858
prop_CLI_parseYesNo def testval val =
1859
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1860
  if testval
1861
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1862
    else let result = CLI.parseYesNo def (Just actual_val)
1863
         in if actual_val `elem` ["yes", "no"]
1864
              then result ==? Types.Ok (actual_val == "yes")
1865
              else property $ Types.isBad result
1866

    
1867
-- | Helper to check for correct parsing of string arg.
1868
checkStringArg :: [Char]
1869
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1870
                   CLI.Options -> Maybe [Char])
1871
               -> Property
1872
checkStringArg val (opt, fn) =
1873
  let GetOpt.Option _ longs _ _ = opt
1874
  in case longs of
1875
       [] -> failTest "no long options?"
1876
       cmdarg:_ ->
1877
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1878
           Left e -> failTest $ "Failed to parse option: " ++ show e
1879
           Right (options, _) -> fn options ==? Just val
1880

    
1881
-- | Test a few string arguments.
1882
prop_CLI_StringArg :: [Char] -> Property
1883
prop_CLI_StringArg argument =
1884
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1885
             , (CLI.oDynuFile,      CLI.optDynuFile)
1886
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1887
             , (CLI.oReplay,        CLI.optReplay)
1888
             , (CLI.oPrintCommands, CLI.optShowCmds)
1889
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1890
             ]
1891
  in conjoin $ map (checkStringArg argument) args
1892

    
1893
-- | Helper to test that a given option is accepted OK with quick exit.
1894
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1895
checkEarlyExit name options param =
1896
  case CLI.parseOptsInner [param] name options of
1897
    Left (code, _) -> if code == 0
1898
                          then property True
1899
                          else failTest $ "Program " ++ name ++
1900
                                 " returns invalid code " ++ show code ++
1901
                                 " for option " ++ param
1902
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1903
         param ++ " as early exit one"
1904

    
1905
-- | Test that all binaries support some common options. There is
1906
-- nothing actually random about this test...
1907
prop_CLI_stdopts :: Property
1908
prop_CLI_stdopts =
1909
  let params = ["-h", "--help", "-V", "--version"]
1910
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1911
      -- apply checkEarlyExit across the cartesian product of params and opts
1912
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1913

    
1914
testSuite "CLI"
1915
          [ 'prop_CLI_parseISpec
1916
          , 'prop_CLI_parseISpecFail
1917
          , 'prop_CLI_parseYesNo
1918
          , 'prop_CLI_StringArg
1919
          , 'prop_CLI_stdopts
1920
          ]
1921

    
1922
-- * JSON tests
1923

    
1924
prop_JSON_toArray :: [Int] -> Property
1925
prop_JSON_toArray intarr =
1926
  let arr = map J.showJSON intarr in
1927
  case JSON.toArray (J.JSArray arr) of
1928
    Types.Ok arr' -> arr ==? arr'
1929
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1930

    
1931
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1932
prop_JSON_toArrayFail i s b =
1933
  -- poor man's instance Arbitrary JSValue
1934
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1935
  case JSON.toArray item of
1936
    Types.Bad _ -> property True
1937
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1938

    
1939
testSuite "JSON"
1940
          [ 'prop_JSON_toArray
1941
          , 'prop_JSON_toArrayFail
1942
          ]
1943

    
1944
-- * Luxi tests
1945

    
1946
instance Arbitrary Luxi.TagObject where
1947
  arbitrary = elements [minBound..maxBound]
1948

    
1949
instance Arbitrary Luxi.LuxiReq where
1950
  arbitrary = elements [minBound..maxBound]
1951

    
1952
instance Arbitrary Luxi.LuxiOp where
1953
  arbitrary = do
1954
    lreq <- arbitrary
1955
    case lreq of
1956
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
1957
      Luxi.ReqQueryFields -> Luxi.QueryFields <$> arbitrary <*> getFields
1958
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1959
                            getFields <*> arbitrary
1960
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1961
                             arbitrary <*> arbitrary
1962
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1963
                                getFields <*> arbitrary
1964
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1965
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1966
                              (listOf getFQDN) <*> arbitrary
1967
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1968
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1969
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary <*> getFQDN
1970
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1971
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1972
                                (resize maxOpCodes arbitrary)
1973
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1974
                                  getFields <*> pure J.JSNull <*>
1975
                                  pure J.JSNull <*> arbitrary
1976
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1977
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1978
                                 arbitrary
1979
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1980
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1981
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1982

    
1983
-- | Simple check that encoding/decoding of LuxiOp works.
1984
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1985
prop_Luxi_CallEncoding op =
1986
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1987

    
1988
-- | Helper to a get a temporary file name.
1989
getTempFileName :: IO FilePath
1990
getTempFileName = do
1991
  tempdir <- getTemporaryDirectory
1992
  (fpath, handle) <- openTempFile tempdir "luxitest"
1993
  _ <- hClose handle
1994
  removeFile fpath
1995
  return fpath
1996

    
1997
-- | Server ping-pong helper.
1998
luxiServerPong :: Luxi.Client -> IO ()
1999
luxiServerPong c = do
2000
  msg <- Luxi.recvMsgExt c
2001
  case msg of
2002
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
2003
    _ -> return ()
2004

    
2005
-- | Client ping-pong helper.
2006
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
2007
luxiClientPong c =
2008
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
2009

    
2010
-- | Monadic check that, given a server socket, we can connect via a
2011
-- client to it, and that we can send a list of arbitrary messages and
2012
-- get back what we sent.
2013
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
2014
prop_Luxi_ClientServer dnschars = monadicIO $ do
2015
  let msgs = map (map dnsGetChar) dnschars
2016
  fpath <- run $ getTempFileName
2017
  -- we need to create the server first, otherwise (if we do it in the
2018
  -- forked thread) the client could try to connect to it before it's
2019
  -- ready
2020
  server <- run $ Luxi.getServer fpath
2021
  -- fork the server responder
2022
  _ <- run . forkIO $
2023
    bracket
2024
      (Luxi.acceptClient server)
2025
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
2026
      luxiServerPong
2027
  replies <- run $
2028
    bracket
2029
      (Luxi.getClient fpath)
2030
      Luxi.closeClient
2031
      (\c -> luxiClientPong c msgs)
2032
  assert $ replies == msgs
2033

    
2034
testSuite "Luxi"
2035
          [ 'prop_Luxi_CallEncoding
2036
          , 'prop_Luxi_ClientServer
2037
          ]
2038

    
2039
-- * Ssconf tests
2040

    
2041
instance Arbitrary Ssconf.SSKey where
2042
  arbitrary = elements [minBound..maxBound]
2043

    
2044
prop_Ssconf_filename :: Ssconf.SSKey -> Property
2045
prop_Ssconf_filename key =
2046
  printTestCase "Key doesn't start with correct prefix" $
2047
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
2048

    
2049
testSuite "Ssconf"
2050
  [ 'prop_Ssconf_filename
2051
  ]
2052

    
2053
-- * Rpc tests
2054

    
2055
-- | Monadic check that, for an offline node and a call that does not
2056
-- offline nodes, we get a OfflineNodeError response.
2057
-- FIXME: We need a way of generalizing this, running it for
2058
-- every call manually will soon get problematic
2059
prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
2060
prop_Rpc_noffl_request_allinstinfo call =
2061
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2062
      res <- run $ Rpc.executeRpcCall [node] call
2063
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2064

    
2065
prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
2066
prop_Rpc_noffl_request_instlist call =
2067
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2068
      res <- run $ Rpc.executeRpcCall [node] call
2069
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2070

    
2071
prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
2072
prop_Rpc_noffl_request_nodeinfo call =
2073
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2074
      res <- run $ Rpc.executeRpcCall [node] call
2075
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2076

    
2077
testSuite "Rpc"
2078
  [ 'prop_Rpc_noffl_request_allinstinfo
2079
  , 'prop_Rpc_noffl_request_instlist
2080
  , 'prop_Rpc_noffl_request_nodeinfo
2081
  ]
2082

    
2083
-- * Qlang tests
2084

    
2085
-- | Tests that serialisation/deserialisation of filters is
2086
-- idempotent.
2087
prop_Qlang_Serialisation :: Property
2088
prop_Qlang_Serialisation =
2089
  forAll genFilter $ \flt ->
2090
  J.readJSON (J.showJSON flt) ==? J.Ok flt
2091

    
2092
testSuite "Qlang"
2093
  [ 'prop_Qlang_Serialisation
2094
  ]
2095

    
2096

    
2097
-- * Confd tests (generic library)
2098

    
2099
instance Arbitrary Confd.ConfdRequestType where
2100
  arbitrary = elements [minBound..maxBound]
2101

    
2102
instance Arbitrary Confd.ConfdReqField where
2103
  arbitrary = elements [minBound..maxBound]
2104

    
2105
instance Arbitrary Confd.ConfdReqQ where
2106
  arbitrary = Confd.ConfdReqQ <$> arbitrary <*> arbitrary <*>
2107
              arbitrary <*> arbitrary
2108

    
2109
instance Arbitrary Confd.ConfdQuery where
2110
  arbitrary = oneof [ pure Confd.EmptyQuery
2111
                    , Confd.PlainQuery <$> getName
2112
                    , Confd.DictQuery <$> arbitrary
2113
                    ]
2114

    
2115
instance Arbitrary Confd.ConfdRequest where
2116
  arbitrary = Confd.ConfdRequest <$> arbitrary <*> arbitrary <*> arbitrary
2117
              <*> arbitrary
2118

    
2119
-- | Test that signing messages and checking signatures is correct. It
2120
-- also tests, indirectly the serialisation of messages so we don't
2121
-- need a separate test for that.
2122
prop_Confd_req_sign :: Hash.HashKey        -- ^ The hash key
2123
                    -> NonNegative Integer -- ^ The base timestamp
2124
                    -> Positive Integer    -- ^ Delta for out of window
2125
                    -> Bool                -- ^ Whether delta should be + or -
2126
                    -> Confd.ConfdRequest
2127
                    -> Property
2128
prop_Confd_req_sign key (NonNegative timestamp) (Positive bad_delta) pm crq =
2129
  forAll (choose (0, fromIntegral C.confdMaxClockSkew)) $ \ good_delta ->
2130
  let encoded = J.encode crq
2131
      salt = show timestamp
2132
      signed = J.encode $ Confd.Utils.signMessage key salt encoded
2133
      good_timestamp = timestamp + if pm then good_delta else (-good_delta)
2134
      bad_delta' = fromIntegral C.confdMaxClockSkew + bad_delta
2135
      bad_timestamp = timestamp + if pm then bad_delta' else (-bad_delta')
2136
      ts_ok = Confd.Utils.parseMessage key signed good_timestamp
2137
      ts_bad = Confd.Utils.parseMessage key signed bad_timestamp
2138
  in printTestCase "Failed to parse good message"
2139
       (ts_ok ==? Types.Ok (encoded, crq)) .&&.
2140
     printTestCase ("Managed to deserialise message with bad\
2141
                    \ timestamp, got " ++ show ts_bad)
2142
       (ts_bad ==? Types.Bad "Too old/too new timestamp or clock skew")
2143

    
2144
-- | Tests that signing with a different key fails detects failure
2145
-- correctly.
2146
prop_Confd_bad_key :: String             -- ^ Salt
2147
                   -> Confd.ConfdRequest -- ^ Request
2148
                   -> Property
2149
prop_Confd_bad_key salt crq =
2150
  -- fixme: we hardcode here the expected length of a sha1 key, as
2151
  -- otherwise we could have two short keys that differ only in the
2152
  -- final zero elements count, and those will be expanded to be the
2153
  -- same
2154
  forAll (vector 20) $ \key_sign ->
2155
  forAll (vector 20 `suchThat` (/= key_sign)) $ \key_verify ->
2156
  let signed = Confd.Utils.signMessage key_sign salt (J.encode crq)
2157
      encoded = J.encode signed
2158
  in printTestCase ("Accepted message signed with different key" ++ encoded) $
2159
    Types.Bad "HMAC verification failed" ==?
2160
     Confd.Utils.parseRequest key_verify encoded
2161

    
2162
testSuite "Confd"
2163
  [ 'prop_Confd_req_sign
2164
  , 'prop_Confd_bad_key
2165
  ]
2166

    
2167
-- * Objects tests
2168

    
2169
-- | Tests that fillDict behaves correctly
2170
prop_Objects_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
2171
prop_Objects_fillDict defaults custom =
2172
  let d_map = Map.fromList defaults
2173
      d_keys = map fst defaults
2174
      c_map = Map.fromList custom
2175
      c_keys = map fst custom
2176
  in printTestCase "Empty custom filling"
2177
      (Objects.fillDict d_map Map.empty [] == d_map) .&&.
2178
     printTestCase "Empty defaults filling"
2179
      (Objects.fillDict Map.empty c_map [] == c_map) .&&.
2180
     printTestCase "Delete all keys"
2181
      (Objects.fillDict d_map c_map (d_keys++c_keys) == Map.empty)
2182

    
2183
testSuite "Objects"
2184
  [ 'prop_Objects_fillDict
2185
  ]