Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 62377cf5

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

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

    
119
import Ganeti.HTools.QCHelper (testSuite)
120

    
121
-- * Constants
122

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

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

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

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

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

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

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

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

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

    
186

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

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

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

    
198
-- * Helper functions
199

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
317
-- * Arbitrary instances
318

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
624
-- * Actual tests
625

    
626
-- ** Utils tests
627

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

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

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

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

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

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

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

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

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

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

    
720
-- ** PeerMap tests
721

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

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

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

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

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

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

    
766
-- ** Container tests
767

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

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

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

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

    
813
-- ** Instance tests
814

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
913
-- ** Backends
914

    
915
-- *** Text backend tests
916

    
917
-- Instance text loader tests
918

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

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

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

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

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

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

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

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

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

    
1077
-- *** Simu backend
1078

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

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

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

    
1130
-- ** Node tests
1131

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1344
-- ** Cluster tests
1345

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1616
-- ** OpCodes tests
1617

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

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

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

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

    
1694
-- ** Jobs tests
1695

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

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

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

    
1714
-- ** Loader tests
1715

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

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

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

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

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

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

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

    
1776
-- ** Types tests
1777

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

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

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

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

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

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

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

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

    
1836
-- ** CLI tests
1837

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

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

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

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

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

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

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

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

    
1920
-- * JSON tests
1921

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

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

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

    
1942
-- * Luxi tests
1943

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

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

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

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

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

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

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

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

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

    
2036
-- * Ssconf tests
2037

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

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

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

    
2050
-- * Rpc tests
2051

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

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

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

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

    
2080
-- * Qlang tests
2081

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

    
2089
testSuite "Qlang"
2090
  [ 'prop_Qlang_Serialisation
2091
  ]