Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 998b6f8b

History | View | Annotate | Download (84.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-}
3

    
4
-- FIXME: should remove the no-warn-unused-imports option, once we get
5
-- around to testing function from all modules; until then, we keep
6
-- the (unused) imports here to generate correct coverage (0 for
7
-- modules we don't use)
8

    
9
{-| Unittests for ganeti-htools.
10

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
16

    
17
This program is free software; you can redistribute it and/or modify
18
it under the terms of the GNU General Public License as published by
19
the Free Software Foundation; either version 2 of the License, or
20
(at your option) any later version.
21

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

    
34
module Ganeti.HTools.QC
35
  ( testUtils
36
  , testPeerMap
37
  , testContainer
38
  , testInstance
39
  , testNode
40
  , testText
41
  , testSimu
42
  , testOpCodes
43
  , testJobs
44
  , testCluster
45
  , testLoader
46
  , testTypes
47
  , testCLI
48
  , testJSON
49
  , testLuxi
50
  , testSsconf
51
  , testRpc
52
  , testQlang
53
  , testConfd
54
  ) where
55

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

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

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

    
120
import Ganeti.HTools.QCHelper (testSuite)
121

    
122
-- * Constants
123

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

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

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

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

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

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

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

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

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

    
187

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

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

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

    
199
-- * Helper functions
200

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
318
-- * Arbitrary instances
319

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
625
-- * Actual tests
626

    
627
-- ** Utils tests
628

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

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

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

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

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

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

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

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

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

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

    
721
-- ** PeerMap tests
722

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

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

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

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

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

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

    
767
-- ** Container tests
768

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

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

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

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

    
814
-- ** Instance tests
815

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
914
-- ** Backends
915

    
916
-- *** Text backend tests
917

    
918
-- Instance text loader tests
919

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

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

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

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

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

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

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

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

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

    
1078
-- *** Simu backend
1079

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

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

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

    
1131
-- ** Node tests
1132

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1345
-- ** Cluster tests
1346

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1617
-- ** OpCodes tests
1618

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

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

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

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

    
1695
-- ** Jobs tests
1696

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

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

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

    
1715
-- ** Loader tests
1716

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

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

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

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

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

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

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

    
1777
-- ** Types tests
1778

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

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

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

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

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

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

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

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

    
1837
-- ** CLI tests
1838

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

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

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

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

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

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

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

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

    
1921
-- * JSON tests
1922

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

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

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

    
1943
-- * Luxi tests
1944

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

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

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

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

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

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

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

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

    
2032
testSuite "Luxi"
2033
          [ 'prop_Luxi_CallEncoding
2034
          , 'prop_Luxi_ClientServer
2035
          ]
2036

    
2037
-- * Ssconf tests
2038

    
2039
instance Arbitrary Ssconf.SSKey where
2040
  arbitrary = elements [minBound..maxBound]
2041

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

    
2047
testSuite "Ssconf"
2048
  [ 'prop_Ssconf_filename
2049
  ]
2050

    
2051
-- * Rpc tests
2052

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

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

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

    
2075
testSuite "Rpc"
2076
  [ 'prop_Rpc_noffl_request_allinstinfo
2077
  , 'prop_Rpc_noffl_request_instlist
2078
  , 'prop_Rpc_noffl_request_nodeinfo
2079
  ]
2080

    
2081
-- * Qlang tests
2082

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

    
2090
testSuite "Qlang"
2091
  [ 'prop_Qlang_Serialisation
2092
  ]
2093

    
2094

    
2095
-- * Confd tests (generic library)
2096

    
2097
instance Arbitrary Confd.ConfdRequestType where
2098
  arbitrary = elements [minBound..maxBound]
2099

    
2100
instance Arbitrary Confd.ConfdReqField where
2101
  arbitrary = elements [minBound..maxBound]
2102

    
2103
instance Arbitrary Confd.ConfdReqQ where
2104
  arbitrary = Confd.ConfdReqQ <$> arbitrary <*> arbitrary <*>
2105
              arbitrary <*> arbitrary
2106

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

    
2113
instance Arbitrary Confd.ConfdRequest where
2114
  arbitrary = Confd.ConfdRequest <$> arbitrary <*> arbitrary <*> arbitrary
2115
              <*> arbitrary
2116

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

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

    
2160
testSuite "Confd"
2161
  [ 'prop_Confd_req_sign
2162
  , 'prop_Confd_bad_key
2163
  ]