Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (78.7 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
  ) where
54

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

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

    
111
import qualified Ganeti.HTools.Program as Program
112
import qualified Ganeti.HTools.Program.Hail
113
import qualified Ganeti.HTools.Program.Hbal
114
import qualified Ganeti.HTools.Program.Hscan
115
import qualified Ganeti.HTools.Program.Hspace
116

    
117
import Ganeti.HTools.QCHelper (testSuite)
118

    
119
-- * Constants
120

    
121
-- | Maximum memory (1TiB, somewhat random value).
122
maxMem :: Int
123
maxMem = 1024 * 1024
124

    
125
-- | Maximum disk (8TiB, somewhat random value).
126
maxDsk :: Int
127
maxDsk = 1024 * 1024 * 8
128

    
129
-- | Max CPUs (1024, somewhat random value).
130
maxCpu :: Int
131
maxCpu = 1024
132

    
133
-- | Max vcpu ratio (random value).
134
maxVcpuRatio :: Double
135
maxVcpuRatio = 1024.0
136

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

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

    
146
-- | Max opcodes or jobs in a submit job and submit many jobs.
147
maxOpCodes :: Int
148
maxOpCodes = 16
149

    
150
-- | All disk templates (used later)
151
allDiskTemplates :: [Types.DiskTemplate]
152
allDiskTemplates = [minBound..maxBound]
153

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

    
184

    
185
defGroup :: Group.Group
186
defGroup = flip Group.setIdx 0 $
187
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
188
                  nullIPolicy
189

    
190
defGroupList :: Group.List
191
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
192

    
193
defGroupAssoc :: Data.Map.Map String Types.Gdx
194
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
195

    
196
-- * Helper functions
197

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

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

    
210
-- | Show a message and fail the test.
211
failTest :: String -> Property
212
failTest msg = printTestCase msg False
213

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

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

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

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

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

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

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

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

    
276
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
277
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
278

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

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

    
305
-- | Checks if an instance is mirrored.
306
isMirrored :: Instance.Instance -> Bool
307
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
308

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

    
315
-- * Arbitrary instances
316

    
317
-- | Defines a DNS name.
318
newtype DNSChar = DNSChar { dnsGetChar::Char }
319

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

    
325
instance Show DNSChar where
326
  show = show . dnsGetChar
327

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

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

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

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

    
357
-- | Defines a tag type.
358
newtype TagChar = TagChar { tagGetChar :: Char }
359

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

    
365
instance Arbitrary TagChar where
366
  arbitrary = do
367
    c <- elements tagChar
368
    return (TagChar c)
369

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

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

    
389
instance Arbitrary Types.InstanceStatus where
390
    arbitrary = elements [minBound..maxBound]
391

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

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

    
412
-- let's generate a random instance
413
instance Arbitrary Instance.Instance where
414
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
415

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

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

    
456
-- and a random node
457
instance Arbitrary Node.Node where
458
  arbitrary = genNode Nothing Nothing
459

    
460
-- replace disks
461
instance Arbitrary OpCodes.ReplaceDisksMode where
462
  arbitrary = elements [minBound..maxBound]
463

    
464
instance Arbitrary OpCodes.DiskIndex where
465
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
466

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

    
485
instance Arbitrary Jobs.OpStatus where
486
  arbitrary = elements [minBound..maxBound]
487

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

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

    
497
instance Arbitrary Types.AllocPolicy where
498
  arbitrary = elements [minBound..maxBound]
499

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

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

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

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

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

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

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

    
565
instance Arbitrary Objects.Hypervisor where
566
  arbitrary = elements [minBound..maxBound]
567

    
568
instance Arbitrary Objects.PartialNDParams where
569
  arbitrary = Objects.PartialNDParams <$> arbitrary <*> arbitrary
570

    
571
instance Arbitrary Objects.Node where
572
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
573
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
574
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
575
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
576
              <*> (Set.fromList <$> genTags)
577

    
578
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
579
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
580

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

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

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

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

    
619
instance Arbitrary Qlang.ItemType where
620
  arbitrary = elements [minBound..maxBound]
621

    
622
-- * Actual tests
623

    
624
-- ** Utils tests
625

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

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

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

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

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

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

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

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

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

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

    
718
-- ** PeerMap tests
719

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

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

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

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

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

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

    
764
-- ** Container tests
765

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

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

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

    
805
testSuite "Container"
806
            [ 'prop_Container_addTwo
807
            , 'prop_Container_nameOf
808
            , 'prop_Container_findByName
809
            ]
810

    
811
-- ** Instance tests
812

    
813
-- Simple instance tests, we only have setter/getters
814

    
815
prop_Instance_creat :: Instance.Instance -> Property
816
prop_Instance_creat inst =
817
  Instance.name inst ==? Instance.alias inst
818

    
819
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
820
prop_Instance_setIdx inst idx =
821
  Instance.idx (Instance.setIdx inst idx) ==? idx
822

    
823
prop_Instance_setName :: Instance.Instance -> String -> Bool
824
prop_Instance_setName inst name =
825
  Instance.name newinst == name &&
826
  Instance.alias newinst == name
827
    where newinst = Instance.setName inst name
828

    
829
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
830
prop_Instance_setAlias inst name =
831
  Instance.name newinst == Instance.name inst &&
832
  Instance.alias newinst == name
833
    where newinst = Instance.setAlias inst name
834

    
835
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
836
prop_Instance_setPri inst pdx =
837
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
838

    
839
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
840
prop_Instance_setSec inst sdx =
841
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
842

    
843
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
844
prop_Instance_setBoth inst pdx sdx =
845
  Instance.pNode si == pdx && Instance.sNode si == sdx
846
    where si = Instance.setBoth inst pdx sdx
847

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

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

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

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

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

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

    
889
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
890
prop_Instance_setMovable inst m =
891
  Instance.movable inst' ==? m
892
    where inst' = Instance.setMovable inst m
893

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

    
911
-- ** Backends
912

    
913
-- *** Text backend tests
914

    
915
-- Instance text loader tests
916

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

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

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

    
999
prop_Text_Load_NodeFail :: [String] -> Property
1000
prop_Text_Load_NodeFail fields =
1001
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
1002

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

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

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

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

    
1064
testSuite "Text"
1065
            [ 'prop_Text_Load_Instance
1066
            , 'prop_Text_Load_InstanceFail
1067
            , 'prop_Text_Load_Node
1068
            , 'prop_Text_Load_NodeFail
1069
            , 'prop_Text_NodeLSIdempotent
1070
            , 'prop_Text_ISpecIdempotent
1071
            , 'prop_Text_IPolicyIdempotent
1072
            , 'prop_Text_CreateSerialise
1073
            ]
1074

    
1075
-- *** Simu backend
1076

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

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

    
1124
testSuite "Simu"
1125
            [ 'prop_Simu_Load
1126
            ]
1127

    
1128
-- ** Node tests
1129

    
1130
prop_Node_setAlias :: Node.Node -> String -> Bool
1131
prop_Node_setAlias node name =
1132
  Node.name newnode == Node.name node &&
1133
  Node.alias newnode == name
1134
    where newnode = Node.setAlias node name
1135

    
1136
prop_Node_setOffline :: Node.Node -> Bool -> Property
1137
prop_Node_setOffline node status =
1138
  Node.offline newnode ==? status
1139
    where newnode = Node.setOffline node status
1140

    
1141
prop_Node_setXmem :: Node.Node -> Int -> Property
1142
prop_Node_setXmem node xm =
1143
  Node.xMem newnode ==? xm
1144
    where newnode = Node.setXmem node xm
1145

    
1146
prop_Node_setMcpu :: Node.Node -> Double -> Property
1147
prop_Node_setMcpu node mc =
1148
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1149
    where newnode = Node.setMcpu node mc
1150

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1342
-- ** Cluster tests
1343

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1614
-- ** OpCodes tests
1615

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

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

    
1639
testSuite "OpCodes"
1640
            [ 'prop_OpCodes_serialization
1641
            , 'case_OpCodes_AllDefined
1642
            ]
1643

    
1644
-- ** Jobs tests
1645

    
1646
-- | Check that (queued) job\/opcode status serialization is idempotent.
1647
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
1648
prop_Jobs_OpStatus_serialization os =
1649
  case J.readJSON (J.showJSON os) of
1650
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1651
    J.Ok os' -> os ==? os'
1652

    
1653
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
1654
prop_Jobs_JobStatus_serialization js =
1655
  case J.readJSON (J.showJSON js) of
1656
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1657
    J.Ok js' -> js ==? js'
1658

    
1659
testSuite "Jobs"
1660
            [ 'prop_Jobs_OpStatus_serialization
1661
            , 'prop_Jobs_JobStatus_serialization
1662
            ]
1663

    
1664
-- ** Loader tests
1665

    
1666
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1667
prop_Loader_lookupNode ktn inst node =
1668
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1669
    where nl = Data.Map.fromList ktn
1670

    
1671
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1672
prop_Loader_lookupInstance kti inst =
1673
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1674
    where il = Data.Map.fromList kti
1675

    
1676
prop_Loader_assignIndices :: Property
1677
prop_Loader_assignIndices =
1678
  -- generate nodes with unique names
1679
  forAll (arbitrary `suchThat`
1680
          (\nodes ->
1681
             let names = map Node.name nodes
1682
             in length names == length (nub names))) $ \nodes ->
1683
  let (nassoc, kt) =
1684
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1685
  in Data.Map.size nassoc == length nodes &&
1686
     Container.size kt == length nodes &&
1687
     if not (null nodes)
1688
       then maximum (IntMap.keys kt) == length nodes - 1
1689
       else True
1690

    
1691
-- | Checks that the number of primary instances recorded on the nodes
1692
-- is zero.
1693
prop_Loader_mergeData :: [Node.Node] -> Bool
1694
prop_Loader_mergeData ns =
1695
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1696
  in case Loader.mergeData [] [] [] []
1697
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1698
    Types.Bad _ -> False
1699
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1700
      let nodes = Container.elems nl
1701
          instances = Container.elems il
1702
      in (sum . map (length . Node.pList)) nodes == 0 &&
1703
         null instances
1704

    
1705
-- | Check that compareNameComponent on equal strings works.
1706
prop_Loader_compareNameComponent_equal :: String -> Bool
1707
prop_Loader_compareNameComponent_equal s =
1708
  BasicTypes.compareNameComponent s s ==
1709
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1710

    
1711
-- | Check that compareNameComponent on prefix strings works.
1712
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1713
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1714
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1715
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1716

    
1717
testSuite "Loader"
1718
            [ 'prop_Loader_lookupNode
1719
            , 'prop_Loader_lookupInstance
1720
            , 'prop_Loader_assignIndices
1721
            , 'prop_Loader_mergeData
1722
            , 'prop_Loader_compareNameComponent_equal
1723
            , 'prop_Loader_compareNameComponent_prefix
1724
            ]
1725

    
1726
-- ** Types tests
1727

    
1728
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1729
prop_Types_AllocPolicy_serialisation apol =
1730
  case J.readJSON (J.showJSON apol) of
1731
    J.Ok p -> p ==? apol
1732
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1733

    
1734
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1735
prop_Types_DiskTemplate_serialisation dt =
1736
  case J.readJSON (J.showJSON dt) of
1737
    J.Ok p -> p ==? dt
1738
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1739

    
1740
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1741
prop_Types_ISpec_serialisation ispec =
1742
  case J.readJSON (J.showJSON ispec) of
1743
    J.Ok p -> p ==? ispec
1744
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1745

    
1746
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1747
prop_Types_IPolicy_serialisation ipol =
1748
  case J.readJSON (J.showJSON ipol) of
1749
    J.Ok p -> p ==? ipol
1750
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1751

    
1752
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1753
prop_Types_EvacMode_serialisation em =
1754
  case J.readJSON (J.showJSON em) of
1755
    J.Ok p -> p ==? em
1756
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1757

    
1758
prop_Types_opToResult :: Types.OpResult Int -> Bool
1759
prop_Types_opToResult op =
1760
  case op of
1761
    Types.OpFail _ -> Types.isBad r
1762
    Types.OpGood v -> case r of
1763
                        Types.Bad _ -> False
1764
                        Types.Ok v' -> v == v'
1765
  where r = Types.opToResult op
1766

    
1767
prop_Types_eitherToResult :: Either String Int -> Bool
1768
prop_Types_eitherToResult ei =
1769
  case ei of
1770
    Left _ -> Types.isBad r
1771
    Right v -> case r of
1772
                 Types.Bad _ -> False
1773
                 Types.Ok v' -> v == v'
1774
    where r = Types.eitherToResult ei
1775

    
1776
testSuite "Types"
1777
            [ 'prop_Types_AllocPolicy_serialisation
1778
            , 'prop_Types_DiskTemplate_serialisation
1779
            , 'prop_Types_ISpec_serialisation
1780
            , 'prop_Types_IPolicy_serialisation
1781
            , 'prop_Types_EvacMode_serialisation
1782
            , 'prop_Types_opToResult
1783
            , 'prop_Types_eitherToResult
1784
            ]
1785

    
1786
-- ** CLI tests
1787

    
1788
-- | Test correct parsing.
1789
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1790
prop_CLI_parseISpec descr dsk mem cpu =
1791
  let str = printf "%d,%d,%d" dsk mem cpu::String
1792
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1793

    
1794
-- | Test parsing failure due to wrong section count.
1795
prop_CLI_parseISpecFail :: String -> Property
1796
prop_CLI_parseISpecFail descr =
1797
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1798
  forAll (replicateM nelems arbitrary) $ \values ->
1799
  let str = intercalate "," $ map show (values::[Int])
1800
  in case CLI.parseISpecString descr str of
1801
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1802
       _ -> property True
1803

    
1804
-- | Test parseYesNo.
1805
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1806
prop_CLI_parseYesNo def testval val =
1807
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1808
  if testval
1809
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1810
    else let result = CLI.parseYesNo def (Just actual_val)
1811
         in if actual_val `elem` ["yes", "no"]
1812
              then result ==? Types.Ok (actual_val == "yes")
1813
              else property $ Types.isBad result
1814

    
1815
-- | Helper to check for correct parsing of string arg.
1816
checkStringArg :: [Char]
1817
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1818
                   CLI.Options -> Maybe [Char])
1819
               -> Property
1820
checkStringArg val (opt, fn) =
1821
  let GetOpt.Option _ longs _ _ = opt
1822
  in case longs of
1823
       [] -> failTest "no long options?"
1824
       cmdarg:_ ->
1825
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1826
           Left e -> failTest $ "Failed to parse option: " ++ show e
1827
           Right (options, _) -> fn options ==? Just val
1828

    
1829
-- | Test a few string arguments.
1830
prop_CLI_StringArg :: [Char] -> Property
1831
prop_CLI_StringArg argument =
1832
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1833
             , (CLI.oDynuFile,      CLI.optDynuFile)
1834
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1835
             , (CLI.oReplay,        CLI.optReplay)
1836
             , (CLI.oPrintCommands, CLI.optShowCmds)
1837
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1838
             ]
1839
  in conjoin $ map (checkStringArg argument) args
1840

    
1841
-- | Helper to test that a given option is accepted OK with quick exit.
1842
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1843
checkEarlyExit name options param =
1844
  case CLI.parseOptsInner [param] name options of
1845
    Left (code, _) -> if code == 0
1846
                          then property True
1847
                          else failTest $ "Program " ++ name ++
1848
                                 " returns invalid code " ++ show code ++
1849
                                 " for option " ++ param
1850
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1851
         param ++ " as early exit one"
1852

    
1853
-- | Test that all binaries support some common options. There is
1854
-- nothing actually random about this test...
1855
prop_CLI_stdopts :: Property
1856
prop_CLI_stdopts =
1857
  let params = ["-h", "--help", "-V", "--version"]
1858
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1859
      -- apply checkEarlyExit across the cartesian product of params and opts
1860
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1861

    
1862
testSuite "CLI"
1863
          [ 'prop_CLI_parseISpec
1864
          , 'prop_CLI_parseISpecFail
1865
          , 'prop_CLI_parseYesNo
1866
          , 'prop_CLI_StringArg
1867
          , 'prop_CLI_stdopts
1868
          ]
1869

    
1870
-- * JSON tests
1871

    
1872
prop_JSON_toArray :: [Int] -> Property
1873
prop_JSON_toArray intarr =
1874
  let arr = map J.showJSON intarr in
1875
  case JSON.toArray (J.JSArray arr) of
1876
    Types.Ok arr' -> arr ==? arr'
1877
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1878

    
1879
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1880
prop_JSON_toArrayFail i s b =
1881
  -- poor man's instance Arbitrary JSValue
1882
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1883
  case JSON.toArray item of
1884
    Types.Bad _ -> property True
1885
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1886

    
1887
testSuite "JSON"
1888
          [ 'prop_JSON_toArray
1889
          , 'prop_JSON_toArrayFail
1890
          ]
1891

    
1892
-- * Luxi tests
1893

    
1894
instance Arbitrary Luxi.TagObject where
1895
  arbitrary = elements [minBound..maxBound]
1896

    
1897
instance Arbitrary Luxi.LuxiReq where
1898
  arbitrary = elements [minBound..maxBound]
1899

    
1900
instance Arbitrary Luxi.LuxiOp where
1901
  arbitrary = do
1902
    lreq <- arbitrary
1903
    case lreq of
1904
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
1905
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1906
                            getFields <*> arbitrary
1907
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1908
                             arbitrary <*> arbitrary
1909
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1910
                                getFields <*> arbitrary
1911
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1912
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1913
                              (listOf getFQDN) <*> arbitrary
1914
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1915
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1916
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary <*> getFQDN
1917
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1918
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1919
                                (resize maxOpCodes arbitrary)
1920
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1921
                                  getFields <*> pure J.JSNull <*>
1922
                                  pure J.JSNull <*> arbitrary
1923
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1924
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1925
                                 arbitrary
1926
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1927
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1928
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1929

    
1930
-- | Simple check that encoding/decoding of LuxiOp works.
1931
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1932
prop_Luxi_CallEncoding op =
1933
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1934

    
1935
-- | Helper to a get a temporary file name.
1936
getTempFileName :: IO FilePath
1937
getTempFileName = do
1938
  tempdir <- getTemporaryDirectory
1939
  (fpath, handle) <- openTempFile tempdir "luxitest"
1940
  _ <- hClose handle
1941
  removeFile fpath
1942
  return fpath
1943

    
1944
-- | Server ping-pong helper.
1945
luxiServerPong :: Luxi.Client -> IO ()
1946
luxiServerPong c = do
1947
  msg <- Luxi.recvMsgExt c
1948
  case msg of
1949
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
1950
    _ -> return ()
1951

    
1952
-- | Client ping-pong helper.
1953
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1954
luxiClientPong c =
1955
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1956

    
1957
-- | Monadic check that, given a server socket, we can connect via a
1958
-- client to it, and that we can send a list of arbitrary messages and
1959
-- get back what we sent.
1960
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1961
prop_Luxi_ClientServer dnschars = monadicIO $ do
1962
  let msgs = map (map dnsGetChar) dnschars
1963
  fpath <- run $ getTempFileName
1964
  -- we need to create the server first, otherwise (if we do it in the
1965
  -- forked thread) the client could try to connect to it before it's
1966
  -- ready
1967
  server <- run $ Luxi.getServer fpath
1968
  -- fork the server responder
1969
  _ <- run . forkIO $
1970
    bracket
1971
      (Luxi.acceptClient server)
1972
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
1973
      luxiServerPong
1974
  replies <- run $
1975
    bracket
1976
      (Luxi.getClient fpath)
1977
      Luxi.closeClient
1978
      (\c -> luxiClientPong c msgs)
1979
  assert $ replies == msgs
1980

    
1981
testSuite "Luxi"
1982
          [ 'prop_Luxi_CallEncoding
1983
          , 'prop_Luxi_ClientServer
1984
          ]
1985

    
1986
-- * Ssconf tests
1987

    
1988
instance Arbitrary Ssconf.SSKey where
1989
  arbitrary = elements [minBound..maxBound]
1990

    
1991
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1992
prop_Ssconf_filename key =
1993
  printTestCase "Key doesn't start with correct prefix" $
1994
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1995

    
1996
testSuite "Ssconf"
1997
  [ 'prop_Ssconf_filename
1998
  ]
1999

    
2000
-- * Rpc tests
2001

    
2002
-- | Monadic check that, for an offline node and a call that does not
2003
-- offline nodes, we get a OfflineNodeError response.
2004
-- FIXME: We need a way of generalizing this, running it for
2005
-- every call manually will soon get problematic
2006
prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
2007
prop_Rpc_noffl_request_allinstinfo call =
2008
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2009
      res <- run $ Rpc.executeRpcCall [node] call
2010
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2011

    
2012
prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
2013
prop_Rpc_noffl_request_instlist call =
2014
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2015
      res <- run $ Rpc.executeRpcCall [node] call
2016
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2017

    
2018
prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
2019
prop_Rpc_noffl_request_nodeinfo call =
2020
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2021
      res <- run $ Rpc.executeRpcCall [node] call
2022
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2023

    
2024
testSuite "Rpc"
2025
  [ 'prop_Rpc_noffl_request_allinstinfo
2026
  , 'prop_Rpc_noffl_request_instlist
2027
  , 'prop_Rpc_noffl_request_nodeinfo
2028
  ]
2029

    
2030
-- * Qlang tests
2031

    
2032
-- | Tests that serialisation/deserialisation of filters is
2033
-- idempotent.
2034
prop_Qlang_Serialisation :: Property
2035
prop_Qlang_Serialisation =
2036
  forAll genFilter $ \flt ->
2037
  J.readJSON (J.showJSON flt) ==? J.Ok flt
2038

    
2039
testSuite "Qlang"
2040
  [ 'prop_Qlang_Serialisation
2041
  ]