Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (76.9 kB)

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

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

    
9
{-| Unittests for ganeti-htools.
10

    
11
-}
12

    
13
{-
14

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

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

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

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

    
32
-}
33

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

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

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

    
106
import qualified Ganeti.HTools.Program as Program
107
import qualified Ganeti.HTools.Program.Hail
108
import qualified Ganeti.HTools.Program.Hbal
109
import qualified Ganeti.HTools.Program.Hscan
110
import qualified Ganeti.HTools.Program.Hspace
111

    
112
import Ganeti.HTools.QCHelper (testSuite)
113

    
114
-- * Constants
115

    
116
-- | Maximum memory (1TiB, somewhat random value).
117
maxMem :: Int
118
maxMem = 1024 * 1024
119

    
120
-- | Maximum disk (8TiB, somewhat random value).
121
maxDsk :: Int
122
maxDsk = 1024 * 1024 * 8
123

    
124
-- | Max CPUs (1024, somewhat random value).
125
maxCpu :: Int
126
maxCpu = 1024
127

    
128
-- | Max vcpu ratio (random value).
129
maxVcpuRatio :: Double
130
maxVcpuRatio = 1024.0
131

    
132
-- | Max spindle ratio (random value).
133
maxSpindleRatio :: Double
134
maxSpindleRatio = 1024.0
135

    
136
-- | Max nodes, used just to limit arbitrary instances for smaller
137
-- opcode definitions (e.g. list of nodes in OpTestDelay).
138
maxNodes :: Int
139
maxNodes = 32
140

    
141
-- | Max opcodes or jobs in a submit job and submit many jobs.
142
maxOpCodes :: Int
143
maxOpCodes = 16
144

    
145
-- | All disk templates (used later)
146
allDiskTemplates :: [Types.DiskTemplate]
147
allDiskTemplates = [minBound..maxBound]
148

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

    
179

    
180
defGroup :: Group.Group
181
defGroup = flip Group.setIdx 0 $
182
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
183
                  nullIPolicy
184

    
185
defGroupList :: Group.List
186
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
187

    
188
defGroupAssoc :: Data.Map.Map String Types.Gdx
189
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
190

    
191
-- * Helper functions
192

    
193
-- | Simple checker for whether OpResult is fail or pass.
194
isFailure :: Types.OpResult a -> Bool
195
isFailure (Types.OpFail _) = True
196
isFailure _ = False
197

    
198
-- | Checks for equality with proper annotation.
199
(==?) :: (Show a, Eq a) => a -> a -> Property
200
(==?) x y = printTestCase
201
            ("Expected equality, but '" ++
202
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
203
infix 3 ==?
204

    
205
-- | Show a message and fail the test.
206
failTest :: String -> Property
207
failTest msg = printTestCase msg False
208

    
209
-- | Update an instance to be smaller than a node.
210
setInstanceSmallerThanNode :: Node.Node
211
                           -> Instance.Instance -> Instance.Instance
212
setInstanceSmallerThanNode node inst =
213
  inst { Instance.mem = Node.availMem node `div` 2
214
       , Instance.dsk = Node.availDisk node `div` 2
215
       , Instance.vcpus = Node.availCpu node `div` 2
216
       }
217

    
218
-- | Create an instance given its spec.
219
createInstance :: Int -> Int -> Int -> Instance.Instance
220
createInstance mem dsk vcpus =
221
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
222
    Types.DTDrbd8 1
223

    
224
-- | Create a small cluster by repeating a node spec.
225
makeSmallCluster :: Node.Node -> Int -> Node.List
226
makeSmallCluster node count =
227
  let origname = Node.name node
228
      origalias = Node.alias node
229
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
230
                                , Node.alias = origalias ++ "-" ++ show idx })
231
              [1..count]
232
      fn = flip Node.buildPeers Container.empty
233
      namelst = map (\n -> (Node.name n, fn n)) nodes
234
      (_, nlst) = Loader.assignIndices namelst
235
  in nlst
236

    
237
-- | Make a small cluster, both nodes and instances.
238
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
239
                      -> (Node.List, Instance.List, Instance.Instance)
240
makeSmallEmptyCluster node count inst =
241
  (makeSmallCluster node count, Container.empty,
242
   setInstanceSmallerThanNode node inst)
243

    
244
-- | Checks if a node is "big" enough.
245
isNodeBig :: Int -> Node.Node -> Bool
246
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
247
                      && Node.availMem node > size * Types.unitMem
248
                      && Node.availCpu node > size * Types.unitCpu
249

    
250
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
251
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
252

    
253
-- | Assigns a new fresh instance to a cluster; this is not
254
-- allocation, so no resource checks are done.
255
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
256
                  Types.Idx -> Types.Idx ->
257
                  (Node.List, Instance.List)
258
assignInstance nl il inst pdx sdx =
259
  let pnode = Container.find pdx nl
260
      snode = Container.find sdx nl
261
      maxiidx = if Container.null il
262
                  then 0
263
                  else fst (Container.findMax il) + 1
264
      inst' = inst { Instance.idx = maxiidx,
265
                     Instance.pNode = pdx, Instance.sNode = sdx }
266
      pnode' = Node.setPri pnode inst'
267
      snode' = Node.setSec snode inst'
268
      nl' = Container.addTwo pdx pnode' sdx snode' nl
269
      il' = Container.add maxiidx inst' il
270
  in (nl', il')
271

    
272
-- | Generates a list of a given size with non-duplicate elements.
273
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
274
genUniquesList cnt =
275
  foldM (\lst _ -> do
276
           newelem <- arbitrary `suchThat` (`notElem` lst)
277
           return (newelem:lst)) [] [1..cnt]
278

    
279
-- | Checks if an instance is mirrored.
280
isMirrored :: Instance.Instance -> Bool
281
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
282

    
283
-- | Returns the possible change node types for a disk template.
284
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
285
evacModeOptions Types.MirrorNone     = []
286
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
287
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
288

    
289
-- * Arbitrary instances
290

    
291
-- | Defines a DNS name.
292
newtype DNSChar = DNSChar { dnsGetChar::Char }
293

    
294
instance Arbitrary DNSChar where
295
  arbitrary = do
296
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
297
    return (DNSChar x)
298

    
299
instance Show DNSChar where
300
  show = show . dnsGetChar
301

    
302
-- | Generates a single name component.
303
getName :: Gen String
304
getName = do
305
  n <- choose (1, 64)
306
  dn <- vector n
307
  return (map dnsGetChar dn)
308

    
309
-- | Generates an entire FQDN.
310
getFQDN :: Gen String
311
getFQDN = do
312
  ncomps <- choose (1, 4)
313
  names <- vectorOf ncomps getName
314
  return $ intercalate "." names
315

    
316
-- | Combinator that generates a 'Maybe' using a sub-combinator.
317
getMaybe :: Gen a -> Gen (Maybe a)
318
getMaybe subgen = do
319
  bool <- arbitrary
320
  if bool
321
    then Just <$> subgen
322
    else return Nothing
323

    
324
-- | Generates a fields list. This uses the same character set as a
325
-- DNS name (just for simplicity).
326
getFields :: Gen [String]
327
getFields = do
328
  n <- choose (1, 32)
329
  vectorOf n getName
330

    
331
-- | Defines a tag type.
332
newtype TagChar = TagChar { tagGetChar :: Char }
333

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

    
339
instance Arbitrary TagChar where
340
  arbitrary = do
341
    c <- elements tagChar
342
    return (TagChar c)
343

    
344
-- | Generates a tag
345
genTag :: Gen [TagChar]
346
genTag = do
347
  -- the correct value would be C.maxTagLen, but that's way too
348
  -- verbose in unittests, and at the moment I don't see any possible
349
  -- bugs with longer tags and the way we use tags in htools
350
  n <- choose (1, 10)
351
  vector n
352

    
353
-- | Generates a list of tags (correctly upper bounded).
354
genTags :: Gen [String]
355
genTags = do
356
  -- the correct value would be C.maxTagsPerObj, but per the comment
357
  -- in genTag, we don't use tags enough in htools to warrant testing
358
  -- such big values
359
  n <- choose (0, 10::Int)
360
  tags <- mapM (const genTag) [1..n]
361
  return $ map (map tagGetChar) tags
362

    
363
instance Arbitrary Types.InstanceStatus where
364
    arbitrary = elements [minBound..maxBound]
365

    
366
-- | Generates a random instance with maximum disk/mem/cpu values.
367
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
368
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
369
  name <- getFQDN
370
  mem <- choose (0, lim_mem)
371
  dsk <- choose (0, lim_dsk)
372
  run_st <- arbitrary
373
  pn <- arbitrary
374
  sn <- arbitrary
375
  vcpus <- choose (0, lim_cpu)
376
  dt <- arbitrary
377
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
378

    
379
-- | Generates an instance smaller than a node.
380
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
381
genInstanceSmallerThanNode node =
382
  genInstanceSmallerThan (Node.availMem node `div` 2)
383
                         (Node.availDisk node `div` 2)
384
                         (Node.availCpu node `div` 2)
385

    
386
-- let's generate a random instance
387
instance Arbitrary Instance.Instance where
388
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
389

    
390
-- | Generas an arbitrary node based on sizing information.
391
genNode :: Maybe Int -- ^ Minimum node size in terms of units
392
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
393
                     -- just by the max... constants)
394
        -> Gen Node.Node
395
genNode min_multiplier max_multiplier = do
396
  let (base_mem, base_dsk, base_cpu) =
397
        case min_multiplier of
398
          Just mm -> (mm * Types.unitMem,
399
                      mm * Types.unitDsk,
400
                      mm * Types.unitCpu)
401
          Nothing -> (0, 0, 0)
402
      (top_mem, top_dsk, top_cpu)  =
403
        case max_multiplier of
404
          Just mm -> (mm * Types.unitMem,
405
                      mm * Types.unitDsk,
406
                      mm * Types.unitCpu)
407
          Nothing -> (maxMem, maxDsk, maxCpu)
408
  name  <- getFQDN
409
  mem_t <- choose (base_mem, top_mem)
410
  mem_f <- choose (base_mem, mem_t)
411
  mem_n <- choose (0, mem_t - mem_f)
412
  dsk_t <- choose (base_dsk, top_dsk)
413
  dsk_f <- choose (base_dsk, dsk_t)
414
  cpu_t <- choose (base_cpu, top_cpu)
415
  offl  <- arbitrary
416
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
417
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
418
      n' = Node.setPolicy nullIPolicy n
419
  return $ Node.buildPeers n' Container.empty
420

    
421
-- | Helper function to generate a sane node.
422
genOnlineNode :: Gen Node.Node
423
genOnlineNode = do
424
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
425
                              not (Node.failN1 n) &&
426
                              Node.availDisk n > 0 &&
427
                              Node.availMem n > 0 &&
428
                              Node.availCpu n > 0)
429

    
430
-- and a random node
431
instance Arbitrary Node.Node where
432
  arbitrary = genNode Nothing Nothing
433

    
434
-- replace disks
435
instance Arbitrary OpCodes.ReplaceDisksMode where
436
  arbitrary = elements [minBound..maxBound]
437

    
438
instance Arbitrary OpCodes.OpCode where
439
  arbitrary = do
440
    op_id <- elements [ "OP_TEST_DELAY"
441
                      , "OP_INSTANCE_REPLACE_DISKS"
442
                      , "OP_INSTANCE_FAILOVER"
443
                      , "OP_INSTANCE_MIGRATE"
444
                      ]
445
    case op_id of
446
      "OP_TEST_DELAY" ->
447
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
448
                 <*> resize maxNodes (listOf getFQDN)
449
      "OP_INSTANCE_REPLACE_DISKS" ->
450
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
451
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
452
      "OP_INSTANCE_FAILOVER" ->
453
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
454
          getMaybe getFQDN
455
      "OP_INSTANCE_MIGRATE" ->
456
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
457
          arbitrary <*> arbitrary <*> getMaybe getFQDN
458
      _ -> fail "Wrong opcode"
459

    
460
instance Arbitrary Jobs.OpStatus where
461
  arbitrary = elements [minBound..maxBound]
462

    
463
instance Arbitrary Jobs.JobStatus where
464
  arbitrary = elements [minBound..maxBound]
465

    
466
newtype SmallRatio = SmallRatio Double deriving Show
467
instance Arbitrary SmallRatio where
468
  arbitrary = do
469
    v <- choose (0, 1)
470
    return $ SmallRatio v
471

    
472
instance Arbitrary Types.AllocPolicy where
473
  arbitrary = elements [minBound..maxBound]
474

    
475
instance Arbitrary Types.DiskTemplate where
476
  arbitrary = elements [minBound..maxBound]
477

    
478
instance Arbitrary Types.FailMode where
479
  arbitrary = elements [minBound..maxBound]
480

    
481
instance Arbitrary Types.EvacMode where
482
  arbitrary = elements [minBound..maxBound]
483

    
484
instance Arbitrary a => Arbitrary (Types.OpResult a) where
485
  arbitrary = arbitrary >>= \c ->
486
              if c
487
                then Types.OpGood <$> arbitrary
488
                else Types.OpFail <$> arbitrary
489

    
490
instance Arbitrary Types.ISpec where
491
  arbitrary = do
492
    mem_s <- arbitrary::Gen (NonNegative Int)
493
    dsk_c <- arbitrary::Gen (NonNegative Int)
494
    dsk_s <- arbitrary::Gen (NonNegative Int)
495
    cpu_c <- arbitrary::Gen (NonNegative Int)
496
    nic_c <- arbitrary::Gen (NonNegative Int)
497
    su    <- arbitrary::Gen (NonNegative Int)
498
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
499
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
500
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
501
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
502
                       , Types.iSpecNicCount   = fromIntegral nic_c
503
                       , Types.iSpecSpindleUse = fromIntegral su
504
                       }
505

    
506
-- | Generates an ispec bigger than the given one.
507
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
508
genBiggerISpec imin = do
509
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
510
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
511
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
512
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
513
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
514
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
515
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
516
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
517
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
518
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
519
                     , Types.iSpecNicCount   = fromIntegral nic_c
520
                     , Types.iSpecSpindleUse = fromIntegral su
521
                     }
522

    
523
instance Arbitrary Types.IPolicy where
524
  arbitrary = do
525
    imin <- arbitrary
526
    istd <- genBiggerISpec imin
527
    imax <- genBiggerISpec istd
528
    num_tmpl <- choose (0, length allDiskTemplates)
529
    dts  <- genUniquesList num_tmpl
530
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
531
    spindle_ratio <- choose (1.0, maxSpindleRatio)
532
    return Types.IPolicy { Types.iPolicyMinSpec = imin
533
                         , Types.iPolicyStdSpec = istd
534
                         , Types.iPolicyMaxSpec = imax
535
                         , Types.iPolicyDiskTemplates = dts
536
                         , Types.iPolicyVcpuRatio = vcpu_ratio
537
                         , Types.iPolicySpindleRatio = spindle_ratio
538
                         }
539

    
540
instance Arbitrary Objects.Hypervisor where
541
  arbitrary = elements [minBound..maxBound]
542

    
543
instance Arbitrary Objects.PartialNDParams where
544
  arbitrary = Objects.PartialNDParams <$> arbitrary <*> arbitrary
545

    
546
instance Arbitrary Objects.Node where
547
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
548
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
549
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
550
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
551

    
552
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
553
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
554

    
555
instance Arbitrary Rpc.RpcCallInstanceList where
556
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
557

    
558
instance Arbitrary Rpc.RpcCallNodeInfo where
559
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
560

    
561
-- | Custom 'Qlang.Filter' generator (top-level), which enforces a
562
-- (sane) limit on the depth of the generated filters.
563
genFilter :: Gen Qlang.Filter
564
genFilter = choose (0, 10) >>= genFilter'
565

    
566
-- | Custom generator for filters that correctly halves the state of
567
-- the generators at each recursive step, per the QuickCheck
568
-- documentation, in order not to run out of memory.
569
genFilter' :: Int -> Gen Qlang.Filter
570
genFilter' 0 =
571
  oneof [ return Qlang.EmptyFilter
572
        , Qlang.TrueFilter     <$> getName
573
        , Qlang.EQFilter       <$> getName <*> value
574
        , Qlang.LTFilter       <$> getName <*> value
575
        , Qlang.GTFilter       <$> getName <*> value
576
        , Qlang.LEFilter       <$> getName <*> value
577
        , Qlang.GEFilter       <$> getName <*> value
578
        , Qlang.RegexpFilter   <$> getName <*> getName
579
        , Qlang.ContainsFilter <$> getName <*> value
580
        ]
581
    where value = oneof [ Qlang.QuotedString <$> getName
582
                        , Qlang.NumericValue <$> arbitrary
583
                        ]
584
genFilter' n = do
585
  oneof [ Qlang.AndFilter  <$> vectorOf n'' (genFilter' n')
586
        , Qlang.OrFilter   <$> vectorOf n'' (genFilter' n')
587
        , Qlang.NotFilter  <$> genFilter' n'
588
        ]
589
  where n' = n `div` 2 -- sub-filter generator size
590
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
591
                       -- so use this for and/or filter list length
592

    
593
-- * Actual tests
594

    
595
-- ** Utils tests
596

    
597
-- | Helper to generate a small string that doesn't contain commas.
598
genNonCommaString :: Gen [Char]
599
genNonCommaString = do
600
  size <- choose (0, 20) -- arbitrary max size
601
  vectorOf size (arbitrary `suchThat` ((/=) ','))
602

    
603
-- | If the list is not just an empty element, and if the elements do
604
-- not contain commas, then join+split should be idempotent.
605
prop_Utils_commaJoinSplit :: Property
606
prop_Utils_commaJoinSplit =
607
  forAll (choose (0, 20)) $ \llen ->
608
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
609
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
610

    
611
-- | Split and join should always be idempotent.
612
prop_Utils_commaSplitJoin :: [Char] -> Property
613
prop_Utils_commaSplitJoin s =
614
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
615

    
616
-- | fromObjWithDefault, we test using the Maybe monad and an integer
617
-- value.
618
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
619
prop_Utils_fromObjWithDefault def_value random_key =
620
  -- a missing key will be returned with the default
621
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
622
  -- a found key will be returned as is, not with default
623
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
624
       random_key (def_value+1) == Just def_value
625

    
626
-- | Test that functional if' behaves like the syntactic sugar if.
627
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
628
prop_Utils_if'if cnd a b =
629
  Utils.if' cnd a b ==? if cnd then a else b
630

    
631
-- | Test basic select functionality
632
prop_Utils_select :: Int      -- ^ Default result
633
                  -> [Int]    -- ^ List of False values
634
                  -> [Int]    -- ^ List of True values
635
                  -> Gen Prop -- ^ Test result
636
prop_Utils_select def lst1 lst2 =
637
  Utils.select def (flist ++ tlist) ==? expectedresult
638
    where expectedresult = Utils.if' (null lst2) def (head lst2)
639
          flist = zip (repeat False) lst1
640
          tlist = zip (repeat True)  lst2
641

    
642
-- | Test basic select functionality with undefined default
643
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
644
                         -> NonEmptyList Int -- ^ List of True values
645
                         -> Gen Prop         -- ^ Test result
646
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
647
  Utils.select undefined (flist ++ tlist) ==? head lst2
648
    where flist = zip (repeat False) lst1
649
          tlist = zip (repeat True)  lst2
650

    
651
-- | Test basic select functionality with undefined list values
652
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
653
                         -> NonEmptyList Int -- ^ List of True values
654
                         -> Gen Prop         -- ^ Test result
655
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
656
  Utils.select undefined cndlist ==? head lst2
657
    where flist = zip (repeat False) lst1
658
          tlist = zip (repeat True)  lst2
659
          cndlist = flist ++ tlist ++ [undefined]
660

    
661
prop_Utils_parseUnit :: NonNegative Int -> Property
662
prop_Utils_parseUnit (NonNegative n) =
663
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
664
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
665
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
666
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
667
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
668
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
669
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
670
  printTestCase "Internal error/overflow?"
671
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
672
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
673
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
674
        n_gb = n_mb * 1000
675
        n_tb = n_gb * 1000
676

    
677
-- | Test list for the Utils module.
678
testSuite "Utils"
679
            [ 'prop_Utils_commaJoinSplit
680
            , 'prop_Utils_commaSplitJoin
681
            , 'prop_Utils_fromObjWithDefault
682
            , 'prop_Utils_if'if
683
            , 'prop_Utils_select
684
            , 'prop_Utils_select_undefd
685
            , 'prop_Utils_select_undefv
686
            , 'prop_Utils_parseUnit
687
            ]
688

    
689
-- ** PeerMap tests
690

    
691
-- | Make sure add is idempotent.
692
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
693
                           -> PeerMap.Key -> PeerMap.Elem -> Property
694
prop_PeerMap_addIdempotent pmap key em =
695
  fn puniq ==? fn (fn puniq)
696
    where fn = PeerMap.add key em
697
          puniq = PeerMap.accumArray const pmap
698

    
699
-- | Make sure remove is idempotent.
700
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
701
prop_PeerMap_removeIdempotent pmap key =
702
  fn puniq ==? fn (fn puniq)
703
    where fn = PeerMap.remove key
704
          puniq = PeerMap.accumArray const pmap
705

    
706
-- | Make sure a missing item returns 0.
707
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
708
prop_PeerMap_findMissing pmap key =
709
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
710
    where puniq = PeerMap.accumArray const pmap
711

    
712
-- | Make sure an added item is found.
713
prop_PeerMap_addFind :: PeerMap.PeerMap
714
                     -> PeerMap.Key -> PeerMap.Elem -> Property
715
prop_PeerMap_addFind pmap key em =
716
  PeerMap.find key (PeerMap.add key em puniq) ==? em
717
    where puniq = PeerMap.accumArray const pmap
718

    
719
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
720
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
721
prop_PeerMap_maxElem pmap =
722
  PeerMap.maxElem puniq ==? if null puniq then 0
723
                              else (maximum . snd . unzip) puniq
724
    where puniq = PeerMap.accumArray const pmap
725

    
726
-- | List of tests for the PeerMap module.
727
testSuite "PeerMap"
728
            [ 'prop_PeerMap_addIdempotent
729
            , 'prop_PeerMap_removeIdempotent
730
            , 'prop_PeerMap_maxElem
731
            , 'prop_PeerMap_addFind
732
            , 'prop_PeerMap_findMissing
733
            ]
734

    
735
-- ** Container tests
736

    
737
-- we silence the following due to hlint bug fixed in later versions
738
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
739
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
740
prop_Container_addTwo cdata i1 i2 =
741
  fn i1 i2 cont == fn i2 i1 cont &&
742
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
743
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
744
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
745

    
746
prop_Container_nameOf :: Node.Node -> Property
747
prop_Container_nameOf node =
748
  let nl = makeSmallCluster node 1
749
      fnode = head (Container.elems nl)
750
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
751

    
752
-- | We test that in a cluster, given a random node, we can find it by
753
-- its name and alias, as long as all names and aliases are unique,
754
-- and that we fail to find a non-existing name.
755
prop_Container_findByName :: Property
756
prop_Container_findByName =
757
  forAll (genNode (Just 1) Nothing) $ \node ->
758
  forAll (choose (1, 20)) $ \ cnt ->
759
  forAll (choose (0, cnt - 1)) $ \ fidx ->
760
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
761
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
762
  let names = zip (take cnt allnames) (drop cnt allnames)
763
      nl = makeSmallCluster node cnt
764
      nodes = Container.elems nl
765
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
766
                                             nn { Node.name = name,
767
                                                  Node.alias = alias }))
768
               $ zip names nodes
769
      nl' = Container.fromList nodes'
770
      target = snd (nodes' !! fidx)
771
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
772
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
773
     printTestCase "Found non-existing name"
774
       (isNothing (Container.findByName nl' othername))
775

    
776
testSuite "Container"
777
            [ 'prop_Container_addTwo
778
            , 'prop_Container_nameOf
779
            , 'prop_Container_findByName
780
            ]
781

    
782
-- ** Instance tests
783

    
784
-- Simple instance tests, we only have setter/getters
785

    
786
prop_Instance_creat :: Instance.Instance -> Property
787
prop_Instance_creat inst =
788
  Instance.name inst ==? Instance.alias inst
789

    
790
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
791
prop_Instance_setIdx inst idx =
792
  Instance.idx (Instance.setIdx inst idx) ==? idx
793

    
794
prop_Instance_setName :: Instance.Instance -> String -> Bool
795
prop_Instance_setName inst name =
796
  Instance.name newinst == name &&
797
  Instance.alias newinst == name
798
    where newinst = Instance.setName inst name
799

    
800
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
801
prop_Instance_setAlias inst name =
802
  Instance.name newinst == Instance.name inst &&
803
  Instance.alias newinst == name
804
    where newinst = Instance.setAlias inst name
805

    
806
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
807
prop_Instance_setPri inst pdx =
808
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
809

    
810
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
811
prop_Instance_setSec inst sdx =
812
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
813

    
814
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
815
prop_Instance_setBoth inst pdx sdx =
816
  Instance.pNode si == pdx && Instance.sNode si == sdx
817
    where si = Instance.setBoth inst pdx sdx
818

    
819
prop_Instance_shrinkMG :: Instance.Instance -> Property
820
prop_Instance_shrinkMG inst =
821
  Instance.mem inst >= 2 * Types.unitMem ==>
822
    case Instance.shrinkByType inst Types.FailMem of
823
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
824
      _ -> False
825

    
826
prop_Instance_shrinkMF :: Instance.Instance -> Property
827
prop_Instance_shrinkMF inst =
828
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
829
    let inst' = inst { Instance.mem = mem}
830
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
831

    
832
prop_Instance_shrinkCG :: Instance.Instance -> Property
833
prop_Instance_shrinkCG inst =
834
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
835
    case Instance.shrinkByType inst Types.FailCPU of
836
      Types.Ok inst' ->
837
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
838
      _ -> False
839

    
840
prop_Instance_shrinkCF :: Instance.Instance -> Property
841
prop_Instance_shrinkCF inst =
842
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
843
    let inst' = inst { Instance.vcpus = vcpus }
844
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
845

    
846
prop_Instance_shrinkDG :: Instance.Instance -> Property
847
prop_Instance_shrinkDG inst =
848
  Instance.dsk inst >= 2 * Types.unitDsk ==>
849
    case Instance.shrinkByType inst Types.FailDisk of
850
      Types.Ok inst' ->
851
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
852
      _ -> False
853

    
854
prop_Instance_shrinkDF :: Instance.Instance -> Property
855
prop_Instance_shrinkDF inst =
856
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
857
    let inst' = inst { Instance.dsk = dsk }
858
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
859

    
860
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
861
prop_Instance_setMovable inst m =
862
  Instance.movable inst' ==? m
863
    where inst' = Instance.setMovable inst m
864

    
865
testSuite "Instance"
866
            [ 'prop_Instance_creat
867
            , 'prop_Instance_setIdx
868
            , 'prop_Instance_setName
869
            , 'prop_Instance_setAlias
870
            , 'prop_Instance_setPri
871
            , 'prop_Instance_setSec
872
            , 'prop_Instance_setBoth
873
            , 'prop_Instance_shrinkMG
874
            , 'prop_Instance_shrinkMF
875
            , 'prop_Instance_shrinkCG
876
            , 'prop_Instance_shrinkCF
877
            , 'prop_Instance_shrinkDG
878
            , 'prop_Instance_shrinkDF
879
            , 'prop_Instance_setMovable
880
            ]
881

    
882
-- ** Backends
883

    
884
-- *** Text backend tests
885

    
886
-- Instance text loader tests
887

    
888
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
889
                        -> NonEmptyList Char -> [Char]
890
                        -> NonNegative Int -> NonNegative Int -> Bool
891
                        -> Types.DiskTemplate -> Int -> Property
892
prop_Text_Load_Instance name mem dsk vcpus status
893
                        (NonEmpty pnode) snode
894
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
895
  pnode /= snode && pdx /= sdx ==>
896
  let vcpus_s = show vcpus
897
      dsk_s = show dsk
898
      mem_s = show mem
899
      su_s = show su
900
      status_s = Types.instanceStatusToRaw status
901
      ndx = if null snode
902
              then [(pnode, pdx)]
903
              else [(pnode, pdx), (snode, sdx)]
904
      nl = Data.Map.fromList ndx
905
      tags = ""
906
      sbal = if autobal then "Y" else "N"
907
      sdt = Types.diskTemplateToRaw dt
908
      inst = Text.loadInst nl
909
             [name, mem_s, dsk_s, vcpus_s, status_s,
910
              sbal, pnode, snode, sdt, tags, su_s]
911
      fail1 = Text.loadInst nl
912
              [name, mem_s, dsk_s, vcpus_s, status_s,
913
               sbal, pnode, pnode, tags]
914
  in case inst of
915
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
916
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
917
                                        \ loading the instance" $
918
               Instance.name i == name &&
919
               Instance.vcpus i == vcpus &&
920
               Instance.mem i == mem &&
921
               Instance.pNode i == pdx &&
922
               Instance.sNode i == (if null snode
923
                                      then Node.noSecondary
924
                                      else sdx) &&
925
               Instance.autoBalance i == autobal &&
926
               Instance.spindleUse i == su &&
927
               Types.isBad fail1
928

    
929
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
930
prop_Text_Load_InstanceFail ktn fields =
931
  length fields /= 10 && length fields /= 11 ==>
932
    case Text.loadInst nl fields of
933
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
934
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
935
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
936
    where nl = Data.Map.fromList ktn
937

    
938
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
939
                    -> Int -> Bool -> Bool
940
prop_Text_Load_Node name tm nm fm td fd tc fo =
941
  let conv v = if v < 0
942
                 then "?"
943
                 else show v
944
      tm_s = conv tm
945
      nm_s = conv nm
946
      fm_s = conv fm
947
      td_s = conv td
948
      fd_s = conv fd
949
      tc_s = conv tc
950
      fo_s = if fo
951
               then "Y"
952
               else "N"
953
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
954
      gid = Group.uuid defGroup
955
  in case Text.loadNode defGroupAssoc
956
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
957
       Nothing -> False
958
       Just (name', node) ->
959
         if fo || any_broken
960
           then Node.offline node
961
           else Node.name node == name' && name' == name &&
962
                Node.alias node == name &&
963
                Node.tMem node == fromIntegral tm &&
964
                Node.nMem node == nm &&
965
                Node.fMem node == fm &&
966
                Node.tDsk node == fromIntegral td &&
967
                Node.fDsk node == fd &&
968
                Node.tCpu node == fromIntegral tc
969

    
970
prop_Text_Load_NodeFail :: [String] -> Property
971
prop_Text_Load_NodeFail fields =
972
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
973

    
974
prop_Text_NodeLSIdempotent :: Property
975
prop_Text_NodeLSIdempotent =
976
  forAll (genNode (Just 1) Nothing) $ \node ->
977
  -- override failN1 to what loadNode returns by default
978
  let n = Node.setPolicy Types.defIPolicy $
979
          node { Node.failN1 = True, Node.offline = False }
980
  in
981
    (Text.loadNode defGroupAssoc.
982
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
983
    Just (Node.name n, n)
984

    
985
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
986
prop_Text_ISpecIdempotent ispec =
987
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
988
       Text.serializeISpec $ ispec of
989
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
990
    Types.Ok ispec' -> ispec ==? ispec'
991

    
992
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
993
prop_Text_IPolicyIdempotent ipol =
994
  case Text.loadIPolicy . Utils.sepSplit '|' $
995
       Text.serializeIPolicy owner ipol of
996
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
997
    Types.Ok res -> (owner, ipol) ==? res
998
  where owner = "dummy"
999

    
1000
-- | This property, while being in the text tests, does more than just
1001
-- test end-to-end the serialisation and loading back workflow; it
1002
-- also tests the Loader.mergeData and the actuall
1003
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
1004
-- allocations, not for the business logic). As such, it's a quite
1005
-- complex and slow test, and that's the reason we restrict it to
1006
-- small cluster sizes.
1007
prop_Text_CreateSerialise :: Property
1008
prop_Text_CreateSerialise =
1009
  forAll genTags $ \ctags ->
1010
  forAll (choose (1, 20)) $ \maxiter ->
1011
  forAll (choose (2, 10)) $ \count ->
1012
  forAll genOnlineNode $ \node ->
1013
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1014
  let nl = makeSmallCluster node count
1015
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1016
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
1017
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
1018
     of
1019
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1020
       Types.Ok (_, _, _, [], _) -> printTestCase
1021
                                    "Failed to allocate: no allocations" False
1022
       Types.Ok (_, nl', il', _, _) ->
1023
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
1024
                     Types.defIPolicy
1025
             saved = Text.serializeCluster cdata
1026
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
1027
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
1028
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
1029
                ctags ==? ctags2 .&&.
1030
                Types.defIPolicy ==? cpol2 .&&.
1031
                il' ==? il2 .&&.
1032
                defGroupList ==? gl2 .&&.
1033
                nl' ==? nl2
1034

    
1035
testSuite "Text"
1036
            [ 'prop_Text_Load_Instance
1037
            , 'prop_Text_Load_InstanceFail
1038
            , 'prop_Text_Load_Node
1039
            , 'prop_Text_Load_NodeFail
1040
            , 'prop_Text_NodeLSIdempotent
1041
            , 'prop_Text_ISpecIdempotent
1042
            , 'prop_Text_IPolicyIdempotent
1043
            , 'prop_Text_CreateSerialise
1044
            ]
1045

    
1046
-- *** Simu backend
1047

    
1048
-- | Generates a tuple of specs for simulation.
1049
genSimuSpec :: Gen (String, Int, Int, Int, Int)
1050
genSimuSpec = do
1051
  pol <- elements [C.allocPolicyPreferred,
1052
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
1053
                  "p", "a", "u"]
1054
 -- should be reasonable (nodes/group), bigger values only complicate
1055
 -- the display of failed tests, and we don't care (in this particular
1056
 -- test) about big node groups
1057
  nodes <- choose (0, 20)
1058
  dsk <- choose (0, maxDsk)
1059
  mem <- choose (0, maxMem)
1060
  cpu <- choose (0, maxCpu)
1061
  return (pol, nodes, dsk, mem, cpu)
1062

    
1063
-- | Checks that given a set of corrects specs, we can load them
1064
-- successfully, and that at high-level the values look right.
1065
prop_SimuLoad :: Property
1066
prop_SimuLoad =
1067
  forAll (choose (0, 10)) $ \ngroups ->
1068
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
1069
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
1070
                                          p n d m c::String) specs
1071
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
1072
      mdc_in = concatMap (\(_, n, d, m, c) ->
1073
                            replicate n (fromIntegral m, fromIntegral d,
1074
                                         fromIntegral c,
1075
                                         fromIntegral m, fromIntegral d))
1076
               specs :: [(Double, Double, Double, Int, Int)]
1077
  in case Simu.parseData strspecs of
1078
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1079
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1080
         let nodes = map snd $ IntMap.toAscList nl
1081
             nidx = map Node.idx nodes
1082
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1083
                                   Node.fMem n, Node.fDsk n)) nodes
1084
         in
1085
         Container.size gl ==? ngroups .&&.
1086
         Container.size nl ==? totnodes .&&.
1087
         Container.size il ==? 0 .&&.
1088
         length tags ==? 0 .&&.
1089
         ipol ==? Types.defIPolicy .&&.
1090
         nidx ==? [1..totnodes] .&&.
1091
         mdc_in ==? mdc_out .&&.
1092
         map Group.iPolicy (Container.elems gl) ==?
1093
             replicate ngroups Types.defIPolicy
1094

    
1095
testSuite "Simu"
1096
            [ 'prop_SimuLoad
1097
            ]
1098

    
1099
-- ** Node tests
1100

    
1101
prop_Node_setAlias :: Node.Node -> String -> Bool
1102
prop_Node_setAlias node name =
1103
  Node.name newnode == Node.name node &&
1104
  Node.alias newnode == name
1105
    where newnode = Node.setAlias node name
1106

    
1107
prop_Node_setOffline :: Node.Node -> Bool -> Property
1108
prop_Node_setOffline node status =
1109
  Node.offline newnode ==? status
1110
    where newnode = Node.setOffline node status
1111

    
1112
prop_Node_setXmem :: Node.Node -> Int -> Property
1113
prop_Node_setXmem node xm =
1114
  Node.xMem newnode ==? xm
1115
    where newnode = Node.setXmem node xm
1116

    
1117
prop_Node_setMcpu :: Node.Node -> Double -> Property
1118
prop_Node_setMcpu node mc =
1119
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1120
    where newnode = Node.setMcpu node mc
1121

    
1122
-- | Check that an instance add with too high memory or disk will be
1123
-- rejected.
1124
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1125
prop_Node_addPriFM node inst =
1126
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1127
  not (Instance.isOffline inst) ==>
1128
  case Node.addPri node inst'' of
1129
    Types.OpFail Types.FailMem -> True
1130
    _ -> False
1131
  where inst' = setInstanceSmallerThanNode node inst
1132
        inst'' = inst' { Instance.mem = Instance.mem inst }
1133

    
1134
-- | Check that adding a primary instance with too much disk fails
1135
-- with type FailDisk.
1136
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1137
prop_Node_addPriFD node inst =
1138
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1139
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1140
  let inst' = setInstanceSmallerThanNode node inst
1141
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1142
                     , Instance.diskTemplate = dt }
1143
  in case Node.addPri node inst'' of
1144
       Types.OpFail Types.FailDisk -> True
1145
       _ -> False
1146

    
1147
-- | Check that adding a primary instance with too many VCPUs fails
1148
-- with type FailCPU.
1149
prop_Node_addPriFC :: Property
1150
prop_Node_addPriFC =
1151
  forAll (choose (1, maxCpu)) $ \extra ->
1152
  forAll genOnlineNode $ \node ->
1153
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1154
  let inst' = setInstanceSmallerThanNode node inst
1155
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1156
  in case Node.addPri node inst'' of
1157
       Types.OpFail Types.FailCPU -> property True
1158
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1159

    
1160
-- | Check that an instance add with too high memory or disk will be
1161
-- rejected.
1162
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1163
prop_Node_addSec node inst pdx =
1164
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1165
    not (Instance.isOffline inst)) ||
1166
   Instance.dsk inst >= Node.fDsk node) &&
1167
  not (Node.failN1 node) ==>
1168
      isFailure (Node.addSec node inst pdx)
1169

    
1170
-- | Check that an offline instance with reasonable disk size but
1171
-- extra mem/cpu can always be added.
1172
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1173
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1174
  forAll genOnlineNode $ \node ->
1175
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1176
  let inst' = inst { Instance.runSt = Types.AdminOffline
1177
                   , Instance.mem = Node.availMem node + extra_mem
1178
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1179
  in case Node.addPri node inst' of
1180
       Types.OpGood _ -> property True
1181
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1182

    
1183
-- | Check that an offline instance with reasonable disk size but
1184
-- extra mem/cpu can always be added.
1185
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1186
                        -> Types.Ndx -> Property
1187
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1188
  forAll genOnlineNode $ \node ->
1189
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1190
  let inst' = inst { Instance.runSt = Types.AdminOffline
1191
                   , Instance.mem = Node.availMem node + extra_mem
1192
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1193
                   , Instance.diskTemplate = Types.DTDrbd8 }
1194
  in case Node.addSec node inst' pdx of
1195
       Types.OpGood _ -> property True
1196
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1197

    
1198
-- | Checks for memory reservation changes.
1199
prop_Node_rMem :: Instance.Instance -> Property
1200
prop_Node_rMem inst =
1201
  not (Instance.isOffline inst) ==>
1202
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1203
  -- ab = auto_balance, nb = non-auto_balance
1204
  -- we use -1 as the primary node of the instance
1205
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1206
                   , Instance.diskTemplate = Types.DTDrbd8 }
1207
      inst_ab = setInstanceSmallerThanNode node inst'
1208
      inst_nb = inst_ab { Instance.autoBalance = False }
1209
      -- now we have the two instances, identical except the
1210
      -- autoBalance attribute
1211
      orig_rmem = Node.rMem node
1212
      inst_idx = Instance.idx inst_ab
1213
      node_add_ab = Node.addSec node inst_ab (-1)
1214
      node_add_nb = Node.addSec node inst_nb (-1)
1215
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1216
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1217
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1218
       (Types.OpGood a_ab, Types.OpGood a_nb,
1219
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1220
         printTestCase "Consistency checks failed" $
1221
           Node.rMem a_ab >  orig_rmem &&
1222
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1223
           Node.rMem a_nb == orig_rmem &&
1224
           Node.rMem d_ab == orig_rmem &&
1225
           Node.rMem d_nb == orig_rmem &&
1226
           -- this is not related to rMem, but as good a place to
1227
           -- test as any
1228
           inst_idx `elem` Node.sList a_ab &&
1229
           inst_idx `notElem` Node.sList d_ab
1230
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1231

    
1232
-- | Check mdsk setting.
1233
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1234
prop_Node_setMdsk node mx =
1235
  Node.loDsk node' >= 0 &&
1236
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1237
  Node.availDisk node' >= 0 &&
1238
  Node.availDisk node' <= Node.fDsk node' &&
1239
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1240
  Node.mDsk node' == mx'
1241
    where node' = Node.setMdsk node mx'
1242
          SmallRatio mx' = mx
1243

    
1244
-- Check tag maps
1245
prop_Node_tagMaps_idempotent :: Property
1246
prop_Node_tagMaps_idempotent =
1247
  forAll genTags $ \tags ->
1248
  Node.delTags (Node.addTags m tags) tags ==? m
1249
    where m = Data.Map.empty
1250

    
1251
prop_Node_tagMaps_reject :: Property
1252
prop_Node_tagMaps_reject =
1253
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1254
  let m = Node.addTags Data.Map.empty tags
1255
  in all (\t -> Node.rejectAddTags m [t]) tags
1256

    
1257
prop_Node_showField :: Node.Node -> Property
1258
prop_Node_showField node =
1259
  forAll (elements Node.defaultFields) $ \ field ->
1260
  fst (Node.showHeader field) /= Types.unknownField &&
1261
  Node.showField node field /= Types.unknownField
1262

    
1263
prop_Node_computeGroups :: [Node.Node] -> Bool
1264
prop_Node_computeGroups nodes =
1265
  let ng = Node.computeGroups nodes
1266
      onlyuuid = map fst ng
1267
  in length nodes == sum (map (length . snd) ng) &&
1268
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1269
     length (nub onlyuuid) == length onlyuuid &&
1270
     (null nodes || not (null ng))
1271

    
1272
-- Check idempotence of add/remove operations
1273
prop_Node_addPri_idempotent :: Property
1274
prop_Node_addPri_idempotent =
1275
  forAll genOnlineNode $ \node ->
1276
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1277
  case Node.addPri node inst of
1278
    Types.OpGood node' -> Node.removePri node' inst ==? node
1279
    _ -> failTest "Can't add instance"
1280

    
1281
prop_Node_addSec_idempotent :: Property
1282
prop_Node_addSec_idempotent =
1283
  forAll genOnlineNode $ \node ->
1284
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1285
  let pdx = Node.idx node + 1
1286
      inst' = Instance.setPri inst pdx
1287
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1288
  in case Node.addSec node inst'' pdx of
1289
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1290
       _ -> failTest "Can't add instance"
1291

    
1292
testSuite "Node"
1293
            [ 'prop_Node_setAlias
1294
            , 'prop_Node_setOffline
1295
            , 'prop_Node_setMcpu
1296
            , 'prop_Node_setXmem
1297
            , 'prop_Node_addPriFM
1298
            , 'prop_Node_addPriFD
1299
            , 'prop_Node_addPriFC
1300
            , 'prop_Node_addSec
1301
            , 'prop_Node_addOfflinePri
1302
            , 'prop_Node_addOfflineSec
1303
            , 'prop_Node_rMem
1304
            , 'prop_Node_setMdsk
1305
            , 'prop_Node_tagMaps_idempotent
1306
            , 'prop_Node_tagMaps_reject
1307
            , 'prop_Node_showField
1308
            , 'prop_Node_computeGroups
1309
            , 'prop_Node_addPri_idempotent
1310
            , 'prop_Node_addSec_idempotent
1311
            ]
1312

    
1313
-- ** Cluster tests
1314

    
1315
-- | Check that the cluster score is close to zero for a homogeneous
1316
-- cluster.
1317
prop_Score_Zero :: Node.Node -> Property
1318
prop_Score_Zero node =
1319
  forAll (choose (1, 1024)) $ \count ->
1320
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1321
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1322
  let fn = Node.buildPeers node Container.empty
1323
      nlst = replicate count fn
1324
      score = Cluster.compCVNodes nlst
1325
  -- we can't say == 0 here as the floating point errors accumulate;
1326
  -- this should be much lower than the default score in CLI.hs
1327
  in score <= 1e-12
1328

    
1329
-- | Check that cluster stats are sane.
1330
prop_CStats_sane :: Property
1331
prop_CStats_sane =
1332
  forAll (choose (1, 1024)) $ \count ->
1333
  forAll genOnlineNode $ \node ->
1334
  let fn = Node.buildPeers node Container.empty
1335
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1336
      nl = Container.fromList nlst
1337
      cstats = Cluster.totalResources nl
1338
  in Cluster.csAdsk cstats >= 0 &&
1339
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1340

    
1341
-- | Check that one instance is allocated correctly, without
1342
-- rebalances needed.
1343
prop_ClusterAlloc_sane :: Instance.Instance -> Property
1344
prop_ClusterAlloc_sane inst =
1345
  forAll (choose (5, 20)) $ \count ->
1346
  forAll genOnlineNode $ \node ->
1347
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1348
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1349
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1350
     Cluster.tryAlloc nl il inst' of
1351
       Types.Bad _ -> False
1352
       Types.Ok as ->
1353
         case Cluster.asSolution as of
1354
           Nothing -> False
1355
           Just (xnl, xi, _, cv) ->
1356
             let il' = Container.add (Instance.idx xi) xi il
1357
                 tbl = Cluster.Table xnl il' cv []
1358
             in not (canBalance tbl True True False)
1359

    
1360
-- | Checks that on a 2-5 node cluster, we can allocate a random
1361
-- instance spec via tiered allocation (whatever the original instance
1362
-- spec), on either one or two nodes. Furthermore, we test that
1363
-- computed allocation statistics are correct.
1364
prop_ClusterCanTieredAlloc :: Instance.Instance -> Property
1365
prop_ClusterCanTieredAlloc inst =
1366
  forAll (choose (2, 5)) $ \count ->
1367
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1368
  let nl = makeSmallCluster node count
1369
      il = Container.empty
1370
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1371
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1372
  in case allocnodes >>= \allocnodes' ->
1373
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1374
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1375
       Types.Ok (_, nl', il', ixes, cstats) ->
1376
         let (ai_alloc, ai_pool, ai_unav) =
1377
               Cluster.computeAllocationDelta
1378
                (Cluster.totalResources nl)
1379
                (Cluster.totalResources nl')
1380
             all_nodes = Container.elems nl
1381
         in property (not (null ixes)) .&&.
1382
            IntMap.size il' ==? length ixes .&&.
1383
            length ixes ==? length cstats .&&.
1384
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1385
              sum (map Node.hiCpu all_nodes) .&&.
1386
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1387
              sum (map Node.tCpu all_nodes) .&&.
1388
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1389
              truncate (sum (map Node.tMem all_nodes)) .&&.
1390
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1391
              truncate (sum (map Node.tDsk all_nodes))
1392

    
1393
-- | Helper function to create a cluster with the given range of nodes
1394
-- and allocate an instance on it.
1395
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1396
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1397
genClusterAlloc count node inst =
1398
  let nl = makeSmallCluster node count
1399
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1400
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1401
     Cluster.tryAlloc nl Container.empty inst of
1402
       Types.Bad _ -> Types.Bad "Can't allocate"
1403
       Types.Ok as ->
1404
         case Cluster.asSolution as of
1405
           Nothing -> Types.Bad "Empty solution?"
1406
           Just (xnl, xi, _, _) ->
1407
             let xil = Container.add (Instance.idx xi) xi Container.empty
1408
             in Types.Ok (xnl, xil, xi)
1409

    
1410
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1411
-- we can also relocate it.
1412
prop_ClusterAllocRelocate :: Property
1413
prop_ClusterAllocRelocate =
1414
  forAll (choose (4, 8)) $ \count ->
1415
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1416
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1417
  case genClusterAlloc count node inst of
1418
    Types.Bad msg -> failTest msg
1419
    Types.Ok (nl, il, inst') ->
1420
      case IAlloc.processRelocate defGroupList nl il
1421
             (Instance.idx inst) 1
1422
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1423
                 then Instance.sNode
1424
                 else Instance.pNode) inst'] of
1425
        Types.Ok _ -> property True
1426
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1427

    
1428
-- | Helper property checker for the result of a nodeEvac or
1429
-- changeGroup operation.
1430
check_EvacMode :: Group.Group -> Instance.Instance
1431
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1432
               -> Property
1433
check_EvacMode grp inst result =
1434
  case result of
1435
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1436
    Types.Ok (_, _, es) ->
1437
      let moved = Cluster.esMoved es
1438
          failed = Cluster.esFailed es
1439
          opcodes = not . null $ Cluster.esOpCodes es
1440
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1441
         failmsg "'opcodes' is null" opcodes .&&.
1442
         case moved of
1443
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1444
                               .&&.
1445
                               failmsg "wrong target group"
1446
                                         (gdx == Group.idx grp)
1447
           v -> failmsg  ("invalid solution: " ++ show v) False
1448
  where failmsg :: String -> Bool -> Property
1449
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1450
        idx = Instance.idx inst
1451

    
1452
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1453
-- we can also node-evacuate it.
1454
prop_ClusterAllocEvacuate :: Property
1455
prop_ClusterAllocEvacuate =
1456
  forAll (choose (4, 8)) $ \count ->
1457
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1458
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1459
  case genClusterAlloc count node inst of
1460
    Types.Bad msg -> failTest msg
1461
    Types.Ok (nl, il, inst') ->
1462
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
1463
                              Cluster.tryNodeEvac defGroupList nl il mode
1464
                                [Instance.idx inst']) .
1465
                              evacModeOptions .
1466
                              Instance.mirrorType $ inst'
1467

    
1468
-- | Checks that on a 4-8 node cluster with two node groups, once we
1469
-- allocate an instance on the first node group, we can also change
1470
-- its group.
1471
prop_ClusterAllocChangeGroup :: Property
1472
prop_ClusterAllocChangeGroup =
1473
  forAll (choose (4, 8)) $ \count ->
1474
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1475
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1476
  case genClusterAlloc count node inst of
1477
    Types.Bad msg -> failTest msg
1478
    Types.Ok (nl, il, inst') ->
1479
      -- we need to add a second node group and nodes to the cluster
1480
      let nl2 = Container.elems $ makeSmallCluster node count
1481
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1482
          maxndx = maximum . map Node.idx $ nl2
1483
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1484
                             , Node.idx = Node.idx n + maxndx }) nl2
1485
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1486
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1487
          nl' = IntMap.union nl nl4
1488
      in check_EvacMode grp2 inst' $
1489
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1490

    
1491
-- | Check that allocating multiple instances on a cluster, then
1492
-- adding an empty node, results in a valid rebalance.
1493
prop_ClusterAllocBalance :: Property
1494
prop_ClusterAllocBalance =
1495
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1496
  forAll (choose (3, 5)) $ \count ->
1497
  not (Node.offline node) && not (Node.failN1 node) ==>
1498
  let nl = makeSmallCluster node count
1499
      (hnode, nl') = IntMap.deleteFindMax nl
1500
      il = Container.empty
1501
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1502
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1503
  in case allocnodes >>= \allocnodes' ->
1504
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1505
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1506
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1507
       Types.Ok (_, xnl, il', _, _) ->
1508
         let ynl = Container.add (Node.idx hnode) hnode xnl
1509
             cv = Cluster.compCV ynl
1510
             tbl = Cluster.Table ynl il' cv []
1511
         in printTestCase "Failed to rebalance" $
1512
            canBalance tbl True True False
1513

    
1514
-- | Checks consistency.
1515
prop_ClusterCheckConsistency :: Node.Node -> Instance.Instance -> Bool
1516
prop_ClusterCheckConsistency node inst =
1517
  let nl = makeSmallCluster node 3
1518
      [node1, node2, node3] = Container.elems nl
1519
      node3' = node3 { Node.group = 1 }
1520
      nl' = Container.add (Node.idx node3') node3' nl
1521
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1522
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1523
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1524
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1525
  in null (ccheck [(0, inst1)]) &&
1526
     null (ccheck [(0, inst2)]) &&
1527
     (not . null $ ccheck [(0, inst3)])
1528

    
1529
-- | For now, we only test that we don't lose instances during the split.
1530
prop_ClusterSplitCluster :: Node.Node -> Instance.Instance -> Property
1531
prop_ClusterSplitCluster node inst =
1532
  forAll (choose (0, 100)) $ \icnt ->
1533
  let nl = makeSmallCluster node 2
1534
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1535
                   (nl, Container.empty) [1..icnt]
1536
      gni = Cluster.splitCluster nl' il'
1537
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1538
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1539
                                 (Container.elems nl'')) gni
1540

    
1541
-- | Helper function to check if we can allocate an instance on a
1542
-- given node list.
1543
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1544
canAllocOn nl reqnodes inst =
1545
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1546
       Cluster.tryAlloc nl (Container.empty) inst of
1547
       Types.Bad _ -> False
1548
       Types.Ok as ->
1549
         case Cluster.asSolution as of
1550
           Nothing -> False
1551
           Just _ -> True
1552

    
1553
-- | Checks that allocation obeys minimum and maximum instance
1554
-- policies. The unittest generates a random node, duplicates it /count/
1555
-- times, and generates a random instance that can be allocated on
1556
-- this mini-cluster; it then checks that after applying a policy that
1557
-- the instance doesn't fits, the allocation fails.
1558
prop_ClusterAllocPolicy :: Node.Node -> Property
1559
prop_ClusterAllocPolicy node =
1560
  -- rqn is the required nodes (1 or 2)
1561
  forAll (choose (1, 2)) $ \rqn ->
1562
  forAll (choose (5, 20)) $ \count ->
1563
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1564
         $ \inst ->
1565
  forAll (arbitrary `suchThat` (isFailure .
1566
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1567
  let node' = Node.setPolicy ipol node
1568
      nl = makeSmallCluster node' count
1569
  in not $ canAllocOn nl rqn inst
1570

    
1571
testSuite "Cluster"
1572
            [ 'prop_Score_Zero
1573
            , 'prop_CStats_sane
1574
            , 'prop_ClusterAlloc_sane
1575
            , 'prop_ClusterCanTieredAlloc
1576
            , 'prop_ClusterAllocRelocate
1577
            , 'prop_ClusterAllocEvacuate
1578
            , 'prop_ClusterAllocChangeGroup
1579
            , 'prop_ClusterAllocBalance
1580
            , 'prop_ClusterCheckConsistency
1581
            , 'prop_ClusterSplitCluster
1582
            , 'prop_ClusterAllocPolicy
1583
            ]
1584

    
1585
-- ** OpCodes tests
1586

    
1587
-- | Check that opcode serialization is idempotent.
1588
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1589
prop_OpCodes_serialization op =
1590
  case J.readJSON (J.showJSON op) of
1591
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1592
    J.Ok op' -> op ==? op'
1593

    
1594
testSuite "OpCodes"
1595
            [ 'prop_OpCodes_serialization ]
1596

    
1597
-- ** Jobs tests
1598

    
1599
-- | Check that (queued) job\/opcode status serialization is idempotent.
1600
prop_OpStatus_serialization :: Jobs.OpStatus -> Property
1601
prop_OpStatus_serialization os =
1602
  case J.readJSON (J.showJSON os) of
1603
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1604
    J.Ok os' -> os ==? os'
1605

    
1606
prop_JobStatus_serialization :: Jobs.JobStatus -> Property
1607
prop_JobStatus_serialization js =
1608
  case J.readJSON (J.showJSON js) of
1609
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1610
    J.Ok js' -> js ==? js'
1611

    
1612
testSuite "Jobs"
1613
            [ 'prop_OpStatus_serialization
1614
            , 'prop_JobStatus_serialization
1615
            ]
1616

    
1617
-- ** Loader tests
1618

    
1619
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1620
prop_Loader_lookupNode ktn inst node =
1621
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1622
    where nl = Data.Map.fromList ktn
1623

    
1624
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1625
prop_Loader_lookupInstance kti inst =
1626
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1627
    where il = Data.Map.fromList kti
1628

    
1629
prop_Loader_assignIndices :: Property
1630
prop_Loader_assignIndices =
1631
  -- generate nodes with unique names
1632
  forAll (arbitrary `suchThat`
1633
          (\nodes ->
1634
             let names = map Node.name nodes
1635
             in length names == length (nub names))) $ \nodes ->
1636
  let (nassoc, kt) =
1637
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1638
  in Data.Map.size nassoc == length nodes &&
1639
     Container.size kt == length nodes &&
1640
     if not (null nodes)
1641
       then maximum (IntMap.keys kt) == length nodes - 1
1642
       else True
1643

    
1644
-- | Checks that the number of primary instances recorded on the nodes
1645
-- is zero.
1646
prop_Loader_mergeData :: [Node.Node] -> Bool
1647
prop_Loader_mergeData ns =
1648
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1649
  in case Loader.mergeData [] [] [] []
1650
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1651
    Types.Bad _ -> False
1652
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1653
      let nodes = Container.elems nl
1654
          instances = Container.elems il
1655
      in (sum . map (length . Node.pList)) nodes == 0 &&
1656
         null instances
1657

    
1658
-- | Check that compareNameComponent on equal strings works.
1659
prop_Loader_compareNameComponent_equal :: String -> Bool
1660
prop_Loader_compareNameComponent_equal s =
1661
  BasicTypes.compareNameComponent s s ==
1662
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1663

    
1664
-- | Check that compareNameComponent on prefix strings works.
1665
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1666
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1667
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1668
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1669

    
1670
testSuite "Loader"
1671
            [ 'prop_Loader_lookupNode
1672
            , 'prop_Loader_lookupInstance
1673
            , 'prop_Loader_assignIndices
1674
            , 'prop_Loader_mergeData
1675
            , 'prop_Loader_compareNameComponent_equal
1676
            , 'prop_Loader_compareNameComponent_prefix
1677
            ]
1678

    
1679
-- ** Types tests
1680

    
1681
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1682
prop_Types_AllocPolicy_serialisation apol =
1683
  case J.readJSON (J.showJSON apol) of
1684
    J.Ok p -> p ==? apol
1685
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1686

    
1687
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1688
prop_Types_DiskTemplate_serialisation dt =
1689
  case J.readJSON (J.showJSON dt) of
1690
    J.Ok p -> p ==? dt
1691
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1692

    
1693
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1694
prop_Types_ISpec_serialisation ispec =
1695
  case J.readJSON (J.showJSON ispec) of
1696
    J.Ok p -> p ==? ispec
1697
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1698

    
1699
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1700
prop_Types_IPolicy_serialisation ipol =
1701
  case J.readJSON (J.showJSON ipol) of
1702
    J.Ok p -> p ==? ipol
1703
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1704

    
1705
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1706
prop_Types_EvacMode_serialisation em =
1707
  case J.readJSON (J.showJSON em) of
1708
    J.Ok p -> p ==? em
1709
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1710

    
1711
prop_Types_opToResult :: Types.OpResult Int -> Bool
1712
prop_Types_opToResult op =
1713
  case op of
1714
    Types.OpFail _ -> Types.isBad r
1715
    Types.OpGood v -> case r of
1716
                        Types.Bad _ -> False
1717
                        Types.Ok v' -> v == v'
1718
  where r = Types.opToResult op
1719

    
1720
prop_Types_eitherToResult :: Either String Int -> Bool
1721
prop_Types_eitherToResult ei =
1722
  case ei of
1723
    Left _ -> Types.isBad r
1724
    Right v -> case r of
1725
                 Types.Bad _ -> False
1726
                 Types.Ok v' -> v == v'
1727
    where r = Types.eitherToResult ei
1728

    
1729
testSuite "Types"
1730
            [ 'prop_Types_AllocPolicy_serialisation
1731
            , 'prop_Types_DiskTemplate_serialisation
1732
            , 'prop_Types_ISpec_serialisation
1733
            , 'prop_Types_IPolicy_serialisation
1734
            , 'prop_Types_EvacMode_serialisation
1735
            , 'prop_Types_opToResult
1736
            , 'prop_Types_eitherToResult
1737
            ]
1738

    
1739
-- ** CLI tests
1740

    
1741
-- | Test correct parsing.
1742
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1743
prop_CLI_parseISpec descr dsk mem cpu =
1744
  let str = printf "%d,%d,%d" dsk mem cpu::String
1745
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1746

    
1747
-- | Test parsing failure due to wrong section count.
1748
prop_CLI_parseISpecFail :: String -> Property
1749
prop_CLI_parseISpecFail descr =
1750
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1751
  forAll (replicateM nelems arbitrary) $ \values ->
1752
  let str = intercalate "," $ map show (values::[Int])
1753
  in case CLI.parseISpecString descr str of
1754
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1755
       _ -> property True
1756

    
1757
-- | Test parseYesNo.
1758
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1759
prop_CLI_parseYesNo def testval val =
1760
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1761
  if testval
1762
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1763
    else let result = CLI.parseYesNo def (Just actual_val)
1764
         in if actual_val `elem` ["yes", "no"]
1765
              then result ==? Types.Ok (actual_val == "yes")
1766
              else property $ Types.isBad result
1767

    
1768
-- | Helper to check for correct parsing of string arg.
1769
checkStringArg :: [Char]
1770
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1771
                   CLI.Options -> Maybe [Char])
1772
               -> Property
1773
checkStringArg val (opt, fn) =
1774
  let GetOpt.Option _ longs _ _ = opt
1775
  in case longs of
1776
       [] -> failTest "no long options?"
1777
       cmdarg:_ ->
1778
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1779
           Left e -> failTest $ "Failed to parse option: " ++ show e
1780
           Right (options, _) -> fn options ==? Just val
1781

    
1782
-- | Test a few string arguments.
1783
prop_CLI_StringArg :: [Char] -> Property
1784
prop_CLI_StringArg argument =
1785
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1786
             , (CLI.oDynuFile,      CLI.optDynuFile)
1787
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1788
             , (CLI.oReplay,        CLI.optReplay)
1789
             , (CLI.oPrintCommands, CLI.optShowCmds)
1790
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1791
             ]
1792
  in conjoin $ map (checkStringArg argument) args
1793

    
1794
-- | Helper to test that a given option is accepted OK with quick exit.
1795
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1796
checkEarlyExit name options param =
1797
  case CLI.parseOptsInner [param] name options of
1798
    Left (code, _) -> if code == 0
1799
                          then property True
1800
                          else failTest $ "Program " ++ name ++
1801
                                 " returns invalid code " ++ show code ++
1802
                                 " for option " ++ param
1803
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1804
         param ++ " as early exit one"
1805

    
1806
-- | Test that all binaries support some common options. There is
1807
-- nothing actually random about this test...
1808
prop_CLI_stdopts :: Property
1809
prop_CLI_stdopts =
1810
  let params = ["-h", "--help", "-V", "--version"]
1811
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1812
      -- apply checkEarlyExit across the cartesian product of params and opts
1813
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1814

    
1815
testSuite "CLI"
1816
          [ 'prop_CLI_parseISpec
1817
          , 'prop_CLI_parseISpecFail
1818
          , 'prop_CLI_parseYesNo
1819
          , 'prop_CLI_StringArg
1820
          , 'prop_CLI_stdopts
1821
          ]
1822

    
1823
-- * JSON tests
1824

    
1825
prop_JSON_toArray :: [Int] -> Property
1826
prop_JSON_toArray intarr =
1827
  let arr = map J.showJSON intarr in
1828
  case JSON.toArray (J.JSArray arr) of
1829
    Types.Ok arr' -> arr ==? arr'
1830
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1831

    
1832
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1833
prop_JSON_toArrayFail i s b =
1834
  -- poor man's instance Arbitrary JSValue
1835
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1836
  case JSON.toArray item of
1837
    Types.Bad _ -> property True
1838
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1839

    
1840
testSuite "JSON"
1841
          [ 'prop_JSON_toArray
1842
          , 'prop_JSON_toArrayFail
1843
          ]
1844

    
1845
-- * Luxi tests
1846

    
1847
instance Arbitrary Luxi.LuxiReq where
1848
  arbitrary = elements [minBound..maxBound]
1849

    
1850
instance Arbitrary Luxi.QrViaLuxi where
1851
  arbitrary = elements [minBound..maxBound]
1852

    
1853
instance Arbitrary Luxi.LuxiOp where
1854
  arbitrary = do
1855
    lreq <- arbitrary
1856
    case lreq of
1857
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
1858
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1859
                            getFields <*> arbitrary
1860
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1861
                             arbitrary <*> arbitrary
1862
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1863
                                getFields <*> arbitrary
1864
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1865
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1866
                              (listOf getFQDN) <*> arbitrary
1867
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1868
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1869
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> getName <*> getFQDN
1870
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1871
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1872
                                (resize maxOpCodes arbitrary)
1873
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1874
                                  getFields <*> pure J.JSNull <*>
1875
                                  pure J.JSNull <*> arbitrary
1876
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1877
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1878
                                 arbitrary
1879
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1880
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1881
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1882

    
1883
-- | Simple check that encoding/decoding of LuxiOp works.
1884
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1885
prop_Luxi_CallEncoding op =
1886
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1887

    
1888
-- | Helper to a get a temporary file name.
1889
getTempFileName :: IO FilePath
1890
getTempFileName = do
1891
  tempdir <- getTemporaryDirectory
1892
  (fpath, handle) <- openTempFile tempdir "luxitest"
1893
  _ <- hClose handle
1894
  removeFile fpath
1895
  return fpath
1896

    
1897
-- | Helper to execute recvMsg but return Nothing if we reach EOF.
1898
handleEOF :: (IO a) -> IO (Maybe a)
1899
handleEOF action =
1900
  catchJust
1901
    (\e -> if isEOFErrorType (ioeGetErrorType e) then Just () else Nothing)
1902
    (liftM Just action)
1903
    (\_ -> return Nothing)
1904

    
1905
-- | Server ping-pong helper.
1906
luxiServerPong :: Luxi.Client -> IO ()
1907
luxiServerPong c = do
1908
  msg <- handleEOF (Luxi.recvMsg c)
1909
  case msg of
1910
    Nothing -> return ()
1911
    Just m -> Luxi.sendMsg c m >> luxiServerPong c
1912

    
1913
-- | Client ping-pong helper.
1914
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1915
luxiClientPong c =
1916
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1917

    
1918
-- | Monadic check that, given a server socket, we can connect via a
1919
-- client to it, and that we can send a list of arbitrary messages and
1920
-- get back what we sent.
1921
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1922
prop_Luxi_ClientServer dnschars = monadicIO $ do
1923
  let msgs = map (map dnsGetChar) dnschars
1924
  fpath <- run $ getTempFileName
1925
  -- we need to create the server first, otherwise (if we do it in the
1926
  -- forked thread) the client could try to connect to it before it's
1927
  -- ready
1928
  server <- run $ Luxi.getServer fpath
1929
  -- fork the server responder
1930
  _ <- run . forkIO $
1931
    bracket
1932
      (Luxi.acceptClient server)
1933
      (\c -> Luxi.closeClient c >> removeFile fpath)
1934
      luxiServerPong
1935
  replies <- run $
1936
    bracket
1937
      (Luxi.getClient fpath)
1938
      Luxi.closeClient
1939
      (\c -> luxiClientPong c msgs)
1940
  assert $ replies == msgs
1941

    
1942
testSuite "LUXI"
1943
          [ 'prop_Luxi_CallEncoding
1944
          , 'prop_Luxi_ClientServer
1945
          ]
1946

    
1947
-- * Ssconf tests
1948

    
1949
instance Arbitrary Ssconf.SSKey where
1950
  arbitrary = elements [minBound..maxBound]
1951

    
1952
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1953
prop_Ssconf_filename key =
1954
  printTestCase "Key doesn't start with correct prefix" $
1955
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1956

    
1957
testSuite "Ssconf"
1958
  [ 'prop_Ssconf_filename
1959
  ]
1960

    
1961
-- * Rpc tests
1962

    
1963
-- | Monadic check that, for an offline node and a call that does not
1964
-- offline nodes, we get a OfflineNodeError response.
1965
-- FIXME: We need a way of generalizing this, running it for
1966
-- every call manually will soon get problematic
1967
prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
1968
prop_Rpc_noffl_request_allinstinfo call =
1969
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1970
      res <- run $ Rpc.executeRpcCall [node] call
1971
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1972

    
1973
prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
1974
prop_Rpc_noffl_request_instlist call =
1975
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1976
      res <- run $ Rpc.executeRpcCall [node] call
1977
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1978

    
1979
prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
1980
prop_Rpc_noffl_request_nodeinfo call =
1981
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
1982
      res <- run $ Rpc.executeRpcCall [node] call
1983
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
1984

    
1985
testSuite "Rpc"
1986
  [ 'prop_Rpc_noffl_request_allinstinfo
1987
  , 'prop_Rpc_noffl_request_instlist
1988
  , 'prop_Rpc_noffl_request_nodeinfo
1989
  ]
1990

    
1991
-- * Qlang tests
1992

    
1993
-- | Tests that serialisation/deserialisation of filters is
1994
-- idempotent.
1995
prop_Qlang_Serialisation :: Property
1996
prop_Qlang_Serialisation =
1997
  forAll genFilter $ \flt ->
1998
  J.readJSON (J.showJSON flt) ==? J.Ok flt
1999

    
2000
testSuite "Qlang"
2001
  [ 'prop_Qlang_Serialisation
2002
  ]