Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (85.3 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 Test.Ganeti.TestHelper (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 <*> arbitrary
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
instance Arbitrary Qlang.FilterRegex where
627
  arbitrary = getName >>= Qlang.mkRegex -- a name should be a good regex
628

    
629
-- * Actual tests
630

    
631
-- ** Utils tests
632

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

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

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

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

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

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

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

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

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

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

    
725
-- ** PeerMap tests
726

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

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

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

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

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

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

    
771
-- ** Container tests
772

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

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

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

    
812
testSuite "Container"
813
            [ 'prop_Container_addTwo
814
            , 'prop_Container_nameOf
815
            , 'prop_Container_findByName
816
            ]
817

    
818
-- ** Instance tests
819

    
820
-- Simple instance tests, we only have setter/getters
821

    
822
prop_Instance_creat :: Instance.Instance -> Property
823
prop_Instance_creat inst =
824
  Instance.name inst ==? Instance.alias inst
825

    
826
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
827
prop_Instance_setIdx inst idx =
828
  Instance.idx (Instance.setIdx inst idx) ==? idx
829

    
830
prop_Instance_setName :: Instance.Instance -> String -> Bool
831
prop_Instance_setName inst name =
832
  Instance.name newinst == name &&
833
  Instance.alias newinst == name
834
    where newinst = Instance.setName inst name
835

    
836
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
837
prop_Instance_setAlias inst name =
838
  Instance.name newinst == Instance.name inst &&
839
  Instance.alias newinst == name
840
    where newinst = Instance.setAlias inst name
841

    
842
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
843
prop_Instance_setPri inst pdx =
844
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
845

    
846
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
847
prop_Instance_setSec inst sdx =
848
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
849

    
850
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
851
prop_Instance_setBoth inst pdx sdx =
852
  Instance.pNode si == pdx && Instance.sNode si == sdx
853
    where si = Instance.setBoth inst pdx sdx
854

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

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

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

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

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

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

    
896
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
897
prop_Instance_setMovable inst m =
898
  Instance.movable inst' ==? m
899
    where inst' = Instance.setMovable inst m
900

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

    
918
-- ** Backends
919

    
920
-- *** Text backend tests
921

    
922
-- Instance text loader tests
923

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

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

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

    
1006
prop_Text_Load_NodeFail :: [String] -> Property
1007
prop_Text_Load_NodeFail fields =
1008
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
1009

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

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

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

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

    
1071
testSuite "Text"
1072
            [ 'prop_Text_Load_Instance
1073
            , 'prop_Text_Load_InstanceFail
1074
            , 'prop_Text_Load_Node
1075
            , 'prop_Text_Load_NodeFail
1076
            , 'prop_Text_NodeLSIdempotent
1077
            , 'prop_Text_ISpecIdempotent
1078
            , 'prop_Text_IPolicyIdempotent
1079
            , 'prop_Text_CreateSerialise
1080
            ]
1081

    
1082
-- *** Simu backend
1083

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

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

    
1131
testSuite "Simu"
1132
            [ 'prop_Simu_Load
1133
            ]
1134

    
1135
-- ** Node tests
1136

    
1137
prop_Node_setAlias :: Node.Node -> String -> Bool
1138
prop_Node_setAlias node name =
1139
  Node.name newnode == Node.name node &&
1140
  Node.alias newnode == name
1141
    where newnode = Node.setAlias node name
1142

    
1143
prop_Node_setOffline :: Node.Node -> Bool -> Property
1144
prop_Node_setOffline node status =
1145
  Node.offline newnode ==? status
1146
    where newnode = Node.setOffline node status
1147

    
1148
prop_Node_setXmem :: Node.Node -> Int -> Property
1149
prop_Node_setXmem node xm =
1150
  Node.xMem newnode ==? xm
1151
    where newnode = Node.setXmem node xm
1152

    
1153
prop_Node_setMcpu :: Node.Node -> Double -> Property
1154
prop_Node_setMcpu node mc =
1155
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1156
    where newnode = Node.setMcpu node mc
1157

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1349
-- ** Cluster tests
1350

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1621
-- ** OpCodes tests
1622

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

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

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

    
1693
testSuite "OpCodes"
1694
            [ 'prop_OpCodes_serialization
1695
            , 'case_OpCodes_AllDefined
1696
            , 'case_OpCodes_py_compat
1697
            ]
1698

    
1699
-- ** Jobs tests
1700

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

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

    
1714
testSuite "Jobs"
1715
            [ 'prop_Jobs_OpStatus_serialization
1716
            , 'prop_Jobs_JobStatus_serialization
1717
            ]
1718

    
1719
-- ** Loader tests
1720

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

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

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

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

    
1760
-- | Check that compareNameComponent on equal strings works.
1761
prop_Loader_compareNameComponent_equal :: String -> Bool
1762
prop_Loader_compareNameComponent_equal s =
1763
  BasicTypes.compareNameComponent s s ==
1764
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1765

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

    
1772
testSuite "Loader"
1773
            [ 'prop_Loader_lookupNode
1774
            , 'prop_Loader_lookupInstance
1775
            , 'prop_Loader_assignIndices
1776
            , 'prop_Loader_mergeData
1777
            , 'prop_Loader_compareNameComponent_equal
1778
            , 'prop_Loader_compareNameComponent_prefix
1779
            ]
1780

    
1781
-- ** Types tests
1782

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

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

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

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

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

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

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

    
1831
testSuite "Types"
1832
            [ 'prop_Types_AllocPolicy_serialisation
1833
            , 'prop_Types_DiskTemplate_serialisation
1834
            , 'prop_Types_ISpec_serialisation
1835
            , 'prop_Types_IPolicy_serialisation
1836
            , 'prop_Types_EvacMode_serialisation
1837
            , 'prop_Types_opToResult
1838
            , 'prop_Types_eitherToResult
1839
            ]
1840

    
1841
-- ** CLI tests
1842

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

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

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

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

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

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

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

    
1917
testSuite "CLI"
1918
          [ 'prop_CLI_parseISpec
1919
          , 'prop_CLI_parseISpecFail
1920
          , 'prop_CLI_parseYesNo
1921
          , 'prop_CLI_StringArg
1922
          , 'prop_CLI_stdopts
1923
          ]
1924

    
1925
-- * JSON tests
1926

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

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

    
1942
testSuite "JSON"
1943
          [ 'prop_JSON_toArray
1944
          , 'prop_JSON_toArrayFail
1945
          ]
1946

    
1947
-- * Luxi tests
1948

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

    
1952
instance Arbitrary Luxi.LuxiReq where
1953
  arbitrary = elements [minBound..maxBound]
1954

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

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

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

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

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

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

    
2037
testSuite "Luxi"
2038
          [ 'prop_Luxi_CallEncoding
2039
          , 'prop_Luxi_ClientServer
2040
          ]
2041

    
2042
-- * Ssconf tests
2043

    
2044
instance Arbitrary Ssconf.SSKey where
2045
  arbitrary = elements [minBound..maxBound]
2046

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

    
2052
testSuite "Ssconf"
2053
  [ 'prop_Ssconf_filename
2054
  ]
2055

    
2056
-- * Rpc tests
2057

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

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

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

    
2080
testSuite "Rpc"
2081
  [ 'prop_Rpc_noffl_request_allinstinfo
2082
  , 'prop_Rpc_noffl_request_instlist
2083
  , 'prop_Rpc_noffl_request_nodeinfo
2084
  ]
2085

    
2086
-- * Qlang tests
2087

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

    
2095
prop_Qlang_FilterRegex_instances :: Qlang.FilterRegex -> Property
2096
prop_Qlang_FilterRegex_instances rex =
2097
  printTestCase "failed JSON encoding"
2098
    (J.readJSON (J.showJSON rex) ==? J.Ok rex) .&&.
2099
  printTestCase "failed read/show instances" (read (show rex) ==? rex)
2100

    
2101
testSuite "Qlang"
2102
  [ 'prop_Qlang_Serialisation
2103
  , 'prop_Qlang_FilterRegex_instances
2104
  ]
2105

    
2106

    
2107
-- * Confd tests (generic library)
2108

    
2109
instance Arbitrary Confd.ConfdRequestType where
2110
  arbitrary = elements [minBound..maxBound]
2111

    
2112
instance Arbitrary Confd.ConfdReqField where
2113
  arbitrary = elements [minBound..maxBound]
2114

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

    
2119
instance Arbitrary Confd.ConfdQuery where
2120
  arbitrary = oneof [ pure Confd.EmptyQuery
2121
                    , Confd.PlainQuery <$> getName
2122
                    , Confd.DictQuery <$> arbitrary
2123
                    ]
2124

    
2125
instance Arbitrary Confd.ConfdRequest where
2126
  arbitrary = Confd.ConfdRequest <$> arbitrary <*> arbitrary <*> arbitrary
2127
              <*> arbitrary
2128

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

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

    
2172
testSuite "Confd"
2173
  [ 'prop_Confd_req_sign
2174
  , 'prop_Confd_bad_key
2175
  ]
2176

    
2177
-- * Objects tests
2178

    
2179
-- | Tests that fillDict behaves correctly
2180
prop_Objects_fillDict :: [(Int, Int)] -> [(Int, Int)] -> Property
2181
prop_Objects_fillDict defaults custom =
2182
  let d_map = Map.fromList defaults
2183
      d_keys = map fst defaults
2184
      c_map = Map.fromList custom
2185
      c_keys = map fst custom
2186
  in printTestCase "Empty custom filling"
2187
      (Objects.fillDict d_map Map.empty [] == d_map) .&&.
2188
     printTestCase "Empty defaults filling"
2189
      (Objects.fillDict Map.empty c_map [] == c_map) .&&.
2190
     printTestCase "Delete all keys"
2191
      (Objects.fillDict d_map c_map (d_keys++c_keys) == Map.empty)
2192

    
2193
testSuite "Objects"
2194
  [ 'prop_Objects_fillDict
2195
  ]