Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 305e174c

History | View | Annotate | Download (76.7 kB)

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

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

    
9
{-| Unittests for ganeti-htools.
10

    
11
-}
12

    
13
{-
14

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

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

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

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

    
32
-}
33

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

    
54
import qualified Test.HUnit as HUnit
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, sort, (\\))
59
import Data.Maybe
60
import qualified Data.Set as Set
61
import Control.Monad
62
import Control.Applicative
63
import qualified System.Console.GetOpt as GetOpt
64
import qualified Text.JSON as J
65
import qualified Data.Map as Map
66
import qualified Data.IntMap as IntMap
67
import Control.Concurrent (forkIO)
68
import Control.Exception (bracket, catchJust)
69
import System.Directory (getTemporaryDirectory, removeFile)
70
import System.Environment (getEnv)
71
import System.Exit (ExitCode(..))
72
import System.IO (hClose, openTempFile)
73
import System.IO.Error (isEOFErrorType, ioeGetErrorType, isDoesNotExistError)
74
import System.Process (readProcessWithExitCode)
75

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

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

    
117
import Test.Ganeti.TestHelper (testSuite)
118
import Test.Ganeti.TestCommon
119

    
120
-- | All disk templates (used later)
121
allDiskTemplates :: [Types.DiskTemplate]
122
allDiskTemplates = [minBound..maxBound]
123

    
124
-- | Null iPolicy, and by null we mean very liberal.
125
nullIPolicy :: Types.IPolicy
126
nullIPolicy = Types.IPolicy
127
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
128
                                       , Types.iSpecCpuCount   = 0
129
                                       , Types.iSpecDiskSize   = 0
130
                                       , Types.iSpecDiskCount  = 0
131
                                       , Types.iSpecNicCount   = 0
132
                                       , Types.iSpecSpindleUse = 0
133
                                       }
134
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
135
                                       , Types.iSpecCpuCount   = maxBound
136
                                       , Types.iSpecDiskSize   = maxBound
137
                                       , Types.iSpecDiskCount  = C.maxDisks
138
                                       , Types.iSpecNicCount   = C.maxNics
139
                                       , Types.iSpecSpindleUse = maxBound
140
                                       }
141
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
142
                                       , Types.iSpecCpuCount   = Types.unitCpu
143
                                       , Types.iSpecDiskSize   = Types.unitDsk
144
                                       , Types.iSpecDiskCount  = 1
145
                                       , Types.iSpecNicCount   = 1
146
                                       , Types.iSpecSpindleUse = 1
147
                                       }
148
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
149
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
150
                                          -- enough to not impact us
151
  , Types.iPolicySpindleRatio = maxSpindleRatio
152
  }
153

    
154

    
155
defGroup :: Group.Group
156
defGroup = flip Group.setIdx 0 $
157
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
158
                  nullIPolicy
159

    
160
defGroupList :: Group.List
161
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
162

    
163
defGroupAssoc :: Map.Map String Types.Gdx
164
defGroupAssoc = Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
165

    
166
-- * Helper functions
167

    
168
-- | Simple checker for whether OpResult is fail or pass.
169
isFailure :: Types.OpResult a -> Bool
170
isFailure (Types.OpFail _) = True
171
isFailure _ = False
172

    
173
-- | Return the python binary to use. If the PYTHON environment
174
-- variable is defined, use its value, otherwise use just \"python\".
175
pythonCmd :: IO String
176
pythonCmd = catchJust (guard . isDoesNotExistError)
177
            (getEnv "PYTHON") (const (return "python"))
178

    
179
-- | Run Python with an expression, returning the exit code, standard
180
-- output and error.
181
runPython :: String -> String -> IO (ExitCode, String, String)
182
runPython expr stdin = do
183
  py_binary <- pythonCmd
184
  readProcessWithExitCode py_binary ["-c", expr] stdin
185

    
186
-- | Check python exit code, and fail via HUnit assertions if
187
-- non-zero. Otherwise, return the standard output.
188
checkPythonResult :: (ExitCode, String, String) -> IO String
189
checkPythonResult (py_code, py_stdout, py_stderr) = do
190
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
191
       ExitSuccess py_code
192
  return py_stdout
193

    
194
-- | Update an instance to be smaller than a node.
195
setInstanceSmallerThanNode :: Node.Node
196
                           -> Instance.Instance -> Instance.Instance
197
setInstanceSmallerThanNode node inst =
198
  inst { Instance.mem = Node.availMem node `div` 2
199
       , Instance.dsk = Node.availDisk node `div` 2
200
       , Instance.vcpus = Node.availCpu node `div` 2
201
       }
202

    
203
-- | Create an instance given its spec.
204
createInstance :: Int -> Int -> Int -> Instance.Instance
205
createInstance mem dsk vcpus =
206
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
207
    Types.DTDrbd8 1
208

    
209
-- | Create a small cluster by repeating a node spec.
210
makeSmallCluster :: Node.Node -> Int -> Node.List
211
makeSmallCluster node count =
212
  let origname = Node.name node
213
      origalias = Node.alias node
214
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
215
                                , Node.alias = origalias ++ "-" ++ show idx })
216
              [1..count]
217
      fn = flip Node.buildPeers Container.empty
218
      namelst = map (\n -> (Node.name n, fn n)) nodes
219
      (_, nlst) = Loader.assignIndices namelst
220
  in nlst
221

    
222
-- | Make a small cluster, both nodes and instances.
223
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
224
                      -> (Node.List, Instance.List, Instance.Instance)
225
makeSmallEmptyCluster node count inst =
226
  (makeSmallCluster node count, Container.empty,
227
   setInstanceSmallerThanNode node inst)
228

    
229
-- | Checks if a node is "big" enough.
230
isNodeBig :: Int -> Node.Node -> Bool
231
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
232
                      && Node.availMem node > size * Types.unitMem
233
                      && Node.availCpu node > size * Types.unitCpu
234

    
235
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
236
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
237

    
238
-- | Assigns a new fresh instance to a cluster; this is not
239
-- allocation, so no resource checks are done.
240
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
241
                  Types.Idx -> Types.Idx ->
242
                  (Node.List, Instance.List)
243
assignInstance nl il inst pdx sdx =
244
  let pnode = Container.find pdx nl
245
      snode = Container.find sdx nl
246
      maxiidx = if Container.null il
247
                  then 0
248
                  else fst (Container.findMax il) + 1
249
      inst' = inst { Instance.idx = maxiidx,
250
                     Instance.pNode = pdx, Instance.sNode = sdx }
251
      pnode' = Node.setPri pnode inst'
252
      snode' = Node.setSec snode inst'
253
      nl' = Container.addTwo pdx pnode' sdx snode' nl
254
      il' = Container.add maxiidx inst' il
255
  in (nl', il')
256

    
257
-- | Generates a list of a given size with non-duplicate elements.
258
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
259
genUniquesList cnt =
260
  foldM (\lst _ -> do
261
           newelem <- arbitrary `suchThat` (`notElem` lst)
262
           return (newelem:lst)) [] [1..cnt]
263

    
264
-- | Checks if an instance is mirrored.
265
isMirrored :: Instance.Instance -> Bool
266
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
267

    
268
-- | Returns the possible change node types for a disk template.
269
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
270
evacModeOptions Types.MirrorNone     = []
271
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
272
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
273

    
274
-- | Generates a fields list. This uses the same character set as a
275
-- DNS name (just for simplicity).
276
getFields :: Gen [String]
277
getFields = do
278
  n <- choose (1, 32)
279
  vectorOf n getName
280

    
281
instance Arbitrary Types.InstanceStatus where
282
    arbitrary = elements [minBound..maxBound]
283

    
284
-- | Generates a random instance with maximum disk/mem/cpu values.
285
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
286
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
287
  name <- getFQDN
288
  mem <- choose (0, lim_mem)
289
  dsk <- choose (0, lim_dsk)
290
  run_st <- arbitrary
291
  pn <- arbitrary
292
  sn <- arbitrary
293
  vcpus <- choose (0, lim_cpu)
294
  dt <- arbitrary
295
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
296

    
297
-- | Generates an instance smaller than a node.
298
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
299
genInstanceSmallerThanNode node =
300
  genInstanceSmallerThan (Node.availMem node `div` 2)
301
                         (Node.availDisk node `div` 2)
302
                         (Node.availCpu node `div` 2)
303

    
304
-- let's generate a random instance
305
instance Arbitrary Instance.Instance where
306
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
307

    
308
-- | Generas an arbitrary node based on sizing information.
309
genNode :: Maybe Int -- ^ Minimum node size in terms of units
310
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
311
                     -- just by the max... constants)
312
        -> Gen Node.Node
313
genNode min_multiplier max_multiplier = do
314
  let (base_mem, base_dsk, base_cpu) =
315
        case min_multiplier of
316
          Just mm -> (mm * Types.unitMem,
317
                      mm * Types.unitDsk,
318
                      mm * Types.unitCpu)
319
          Nothing -> (0, 0, 0)
320
      (top_mem, top_dsk, top_cpu)  =
321
        case max_multiplier of
322
          Just mm -> (mm * Types.unitMem,
323
                      mm * Types.unitDsk,
324
                      mm * Types.unitCpu)
325
          Nothing -> (maxMem, maxDsk, maxCpu)
326
  name  <- getFQDN
327
  mem_t <- choose (base_mem, top_mem)
328
  mem_f <- choose (base_mem, mem_t)
329
  mem_n <- choose (0, mem_t - mem_f)
330
  dsk_t <- choose (base_dsk, top_dsk)
331
  dsk_f <- choose (base_dsk, dsk_t)
332
  cpu_t <- choose (base_cpu, top_cpu)
333
  offl  <- arbitrary
334
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
335
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
336
      n' = Node.setPolicy nullIPolicy n
337
  return $ Node.buildPeers n' Container.empty
338

    
339
-- | Helper function to generate a sane node.
340
genOnlineNode :: Gen Node.Node
341
genOnlineNode = do
342
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
343
                              not (Node.failN1 n) &&
344
                              Node.availDisk n > 0 &&
345
                              Node.availMem n > 0 &&
346
                              Node.availCpu n > 0)
347

    
348
-- and a random node
349
instance Arbitrary Node.Node where
350
  arbitrary = genNode Nothing Nothing
351

    
352
-- replace disks
353
instance Arbitrary OpCodes.ReplaceDisksMode where
354
  arbitrary = elements [minBound..maxBound]
355

    
356
instance Arbitrary OpCodes.DiskIndex where
357
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
358

    
359
instance Arbitrary OpCodes.OpCode where
360
  arbitrary = do
361
    op_id <- elements OpCodes.allOpIDs
362
    case op_id of
363
      "OP_TEST_DELAY" ->
364
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
365
                 <*> resize maxNodes (listOf getFQDN)
366
      "OP_INSTANCE_REPLACE_DISKS" ->
367
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
368
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
369
      "OP_INSTANCE_FAILOVER" ->
370
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
371
          getMaybe getFQDN
372
      "OP_INSTANCE_MIGRATE" ->
373
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
374
          arbitrary <*> arbitrary <*> getMaybe getFQDN
375
      _ -> fail "Wrong opcode"
376

    
377
instance Arbitrary Jobs.OpStatus where
378
  arbitrary = elements [minBound..maxBound]
379

    
380
instance Arbitrary Jobs.JobStatus where
381
  arbitrary = elements [minBound..maxBound]
382

    
383
newtype SmallRatio = SmallRatio Double deriving Show
384
instance Arbitrary SmallRatio where
385
  arbitrary = do
386
    v <- choose (0, 1)
387
    return $ SmallRatio v
388

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

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

    
395
instance Arbitrary Types.FailMode where
396
  arbitrary = elements [minBound..maxBound]
397

    
398
instance Arbitrary Types.EvacMode where
399
  arbitrary = elements [minBound..maxBound]
400

    
401
instance Arbitrary a => Arbitrary (Types.OpResult a) where
402
  arbitrary = arbitrary >>= \c ->
403
              if c
404
                then Types.OpGood <$> arbitrary
405
                else Types.OpFail <$> arbitrary
406

    
407
instance Arbitrary Types.ISpec where
408
  arbitrary = do
409
    mem_s <- arbitrary::Gen (NonNegative Int)
410
    dsk_c <- arbitrary::Gen (NonNegative Int)
411
    dsk_s <- arbitrary::Gen (NonNegative Int)
412
    cpu_c <- arbitrary::Gen (NonNegative Int)
413
    nic_c <- arbitrary::Gen (NonNegative Int)
414
    su    <- arbitrary::Gen (NonNegative Int)
415
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
416
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
417
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
418
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
419
                       , Types.iSpecNicCount   = fromIntegral nic_c
420
                       , Types.iSpecSpindleUse = fromIntegral su
421
                       }
422

    
423
-- | Generates an ispec bigger than the given one.
424
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
425
genBiggerISpec imin = do
426
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
427
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
428
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
429
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
430
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
431
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
432
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
433
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
434
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
435
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
436
                     , Types.iSpecNicCount   = fromIntegral nic_c
437
                     , Types.iSpecSpindleUse = fromIntegral su
438
                     }
439

    
440
instance Arbitrary Types.IPolicy where
441
  arbitrary = do
442
    imin <- arbitrary
443
    istd <- genBiggerISpec imin
444
    imax <- genBiggerISpec istd
445
    num_tmpl <- choose (0, length allDiskTemplates)
446
    dts  <- genUniquesList num_tmpl
447
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
448
    spindle_ratio <- choose (1.0, maxSpindleRatio)
449
    return Types.IPolicy { Types.iPolicyMinSpec = imin
450
                         , Types.iPolicyStdSpec = istd
451
                         , Types.iPolicyMaxSpec = imax
452
                         , Types.iPolicyDiskTemplates = dts
453
                         , Types.iPolicyVcpuRatio = vcpu_ratio
454
                         , Types.iPolicySpindleRatio = spindle_ratio
455
                         }
456

    
457
-- | Custom 'Qlang.Filter' generator (top-level), which enforces a
458
-- (sane) limit on the depth of the generated filters.
459
genFilter :: Gen (Qlang.Filter Qlang.FilterField)
460
genFilter = choose (0, 10) >>= genFilter'
461

    
462
-- | Custom generator for filters that correctly halves the state of
463
-- the generators at each recursive step, per the QuickCheck
464
-- documentation, in order not to run out of memory.
465
genFilter' :: Int -> Gen (Qlang.Filter Qlang.FilterField)
466
genFilter' 0 =
467
  oneof [ return Qlang.EmptyFilter
468
        , Qlang.TrueFilter     <$> getName
469
        , Qlang.EQFilter       <$> getName <*> value
470
        , Qlang.LTFilter       <$> getName <*> value
471
        , Qlang.GTFilter       <$> getName <*> value
472
        , Qlang.LEFilter       <$> getName <*> value
473
        , Qlang.GEFilter       <$> getName <*> value
474
        , Qlang.RegexpFilter   <$> getName <*> arbitrary
475
        , Qlang.ContainsFilter <$> getName <*> value
476
        ]
477
    where value = oneof [ Qlang.QuotedString <$> getName
478
                        , Qlang.NumericValue <$> arbitrary
479
                        ]
480
genFilter' n = do
481
  oneof [ Qlang.AndFilter  <$> vectorOf n'' (genFilter' n')
482
        , Qlang.OrFilter   <$> vectorOf n'' (genFilter' n')
483
        , Qlang.NotFilter  <$> genFilter' n'
484
        ]
485
  where n' = n `div` 2 -- sub-filter generator size
486
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
487
                       -- so use this for and/or filter list length
488

    
489
instance Arbitrary Qlang.ItemType where
490
  arbitrary = elements [minBound..maxBound]
491

    
492
instance Arbitrary Qlang.FilterRegex where
493
  arbitrary = getName >>= Qlang.mkRegex -- a name should be a good regex
494

    
495
-- * Actual tests
496

    
497
-- ** Utils tests
498

    
499
-- | Helper to generate a small string that doesn't contain commas.
500
genNonCommaString :: Gen [Char]
501
genNonCommaString = do
502
  size <- choose (0, 20) -- arbitrary max size
503
  vectorOf size (arbitrary `suchThat` ((/=) ','))
504

    
505
-- | If the list is not just an empty element, and if the elements do
506
-- not contain commas, then join+split should be idempotent.
507
prop_Utils_commaJoinSplit :: Property
508
prop_Utils_commaJoinSplit =
509
  forAll (choose (0, 20)) $ \llen ->
510
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
511
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
512

    
513
-- | Split and join should always be idempotent.
514
prop_Utils_commaSplitJoin :: [Char] -> Property
515
prop_Utils_commaSplitJoin s =
516
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
517

    
518
-- | fromObjWithDefault, we test using the Maybe monad and an integer
519
-- value.
520
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
521
prop_Utils_fromObjWithDefault def_value random_key =
522
  -- a missing key will be returned with the default
523
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
524
  -- a found key will be returned as is, not with default
525
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
526
       random_key (def_value+1) == Just def_value
527

    
528
-- | Test that functional if' behaves like the syntactic sugar if.
529
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
530
prop_Utils_if'if cnd a b =
531
  Utils.if' cnd a b ==? if cnd then a else b
532

    
533
-- | Test basic select functionality
534
prop_Utils_select :: Int      -- ^ Default result
535
                  -> [Int]    -- ^ List of False values
536
                  -> [Int]    -- ^ List of True values
537
                  -> Gen Prop -- ^ Test result
538
prop_Utils_select def lst1 lst2 =
539
  Utils.select def (flist ++ tlist) ==? expectedresult
540
    where expectedresult = Utils.if' (null lst2) def (head lst2)
541
          flist = zip (repeat False) lst1
542
          tlist = zip (repeat True)  lst2
543

    
544
-- | Test basic select functionality with undefined default
545
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
546
                         -> NonEmptyList Int -- ^ List of True values
547
                         -> Gen Prop         -- ^ Test result
548
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
549
  Utils.select undefined (flist ++ tlist) ==? head lst2
550
    where flist = zip (repeat False) lst1
551
          tlist = zip (repeat True)  lst2
552

    
553
-- | Test basic select functionality with undefined list values
554
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
555
                         -> NonEmptyList Int -- ^ List of True values
556
                         -> Gen Prop         -- ^ Test result
557
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
558
  Utils.select undefined cndlist ==? head lst2
559
    where flist = zip (repeat False) lst1
560
          tlist = zip (repeat True)  lst2
561
          cndlist = flist ++ tlist ++ [undefined]
562

    
563
prop_Utils_parseUnit :: NonNegative Int -> Property
564
prop_Utils_parseUnit (NonNegative n) =
565
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
566
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
567
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
568
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
569
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
570
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
571
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
572
  printTestCase "Internal error/overflow?"
573
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
574
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
575
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
576
        n_gb = n_mb * 1000
577
        n_tb = n_gb * 1000
578

    
579
-- | Test list for the Utils module.
580
testSuite "Utils"
581
            [ 'prop_Utils_commaJoinSplit
582
            , 'prop_Utils_commaSplitJoin
583
            , 'prop_Utils_fromObjWithDefault
584
            , 'prop_Utils_if'if
585
            , 'prop_Utils_select
586
            , 'prop_Utils_select_undefd
587
            , 'prop_Utils_select_undefv
588
            , 'prop_Utils_parseUnit
589
            ]
590

    
591
-- ** PeerMap tests
592

    
593
-- | Make sure add is idempotent.
594
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
595
                           -> PeerMap.Key -> PeerMap.Elem -> Property
596
prop_PeerMap_addIdempotent pmap key em =
597
  fn puniq ==? fn (fn puniq)
598
    where fn = PeerMap.add key em
599
          puniq = PeerMap.accumArray const pmap
600

    
601
-- | Make sure remove is idempotent.
602
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
603
prop_PeerMap_removeIdempotent pmap key =
604
  fn puniq ==? fn (fn puniq)
605
    where fn = PeerMap.remove key
606
          puniq = PeerMap.accumArray const pmap
607

    
608
-- | Make sure a missing item returns 0.
609
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
610
prop_PeerMap_findMissing pmap key =
611
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
612
    where puniq = PeerMap.accumArray const pmap
613

    
614
-- | Make sure an added item is found.
615
prop_PeerMap_addFind :: PeerMap.PeerMap
616
                     -> PeerMap.Key -> PeerMap.Elem -> Property
617
prop_PeerMap_addFind pmap key em =
618
  PeerMap.find key (PeerMap.add key em puniq) ==? em
619
    where puniq = PeerMap.accumArray const pmap
620

    
621
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
622
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
623
prop_PeerMap_maxElem pmap =
624
  PeerMap.maxElem puniq ==? if null puniq then 0
625
                              else (maximum . snd . unzip) puniq
626
    where puniq = PeerMap.accumArray const pmap
627

    
628
-- | List of tests for the PeerMap module.
629
testSuite "PeerMap"
630
            [ 'prop_PeerMap_addIdempotent
631
            , 'prop_PeerMap_removeIdempotent
632
            , 'prop_PeerMap_maxElem
633
            , 'prop_PeerMap_addFind
634
            , 'prop_PeerMap_findMissing
635
            ]
636

    
637
-- ** Container tests
638

    
639
-- we silence the following due to hlint bug fixed in later versions
640
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
641
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
642
prop_Container_addTwo cdata i1 i2 =
643
  fn i1 i2 cont == fn i2 i1 cont &&
644
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
645
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
646
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
647

    
648
prop_Container_nameOf :: Node.Node -> Property
649
prop_Container_nameOf node =
650
  let nl = makeSmallCluster node 1
651
      fnode = head (Container.elems nl)
652
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
653

    
654
-- | We test that in a cluster, given a random node, we can find it by
655
-- its name and alias, as long as all names and aliases are unique,
656
-- and that we fail to find a non-existing name.
657
prop_Container_findByName :: Property
658
prop_Container_findByName =
659
  forAll (genNode (Just 1) Nothing) $ \node ->
660
  forAll (choose (1, 20)) $ \ cnt ->
661
  forAll (choose (0, cnt - 1)) $ \ fidx ->
662
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
663
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
664
  let names = zip (take cnt allnames) (drop cnt allnames)
665
      nl = makeSmallCluster node cnt
666
      nodes = Container.elems nl
667
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
668
                                             nn { Node.name = name,
669
                                                  Node.alias = alias }))
670
               $ zip names nodes
671
      nl' = Container.fromList nodes'
672
      target = snd (nodes' !! fidx)
673
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
674
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
675
     printTestCase "Found non-existing name"
676
       (isNothing (Container.findByName nl' othername))
677

    
678
testSuite "Container"
679
            [ 'prop_Container_addTwo
680
            , 'prop_Container_nameOf
681
            , 'prop_Container_findByName
682
            ]
683

    
684
-- ** Instance tests
685

    
686
-- Simple instance tests, we only have setter/getters
687

    
688
prop_Instance_creat :: Instance.Instance -> Property
689
prop_Instance_creat inst =
690
  Instance.name inst ==? Instance.alias inst
691

    
692
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
693
prop_Instance_setIdx inst idx =
694
  Instance.idx (Instance.setIdx inst idx) ==? idx
695

    
696
prop_Instance_setName :: Instance.Instance -> String -> Bool
697
prop_Instance_setName inst name =
698
  Instance.name newinst == name &&
699
  Instance.alias newinst == name
700
    where newinst = Instance.setName inst name
701

    
702
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
703
prop_Instance_setAlias inst name =
704
  Instance.name newinst == Instance.name inst &&
705
  Instance.alias newinst == name
706
    where newinst = Instance.setAlias inst name
707

    
708
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
709
prop_Instance_setPri inst pdx =
710
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
711

    
712
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
713
prop_Instance_setSec inst sdx =
714
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
715

    
716
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
717
prop_Instance_setBoth inst pdx sdx =
718
  Instance.pNode si == pdx && Instance.sNode si == sdx
719
    where si = Instance.setBoth inst pdx sdx
720

    
721
prop_Instance_shrinkMG :: Instance.Instance -> Property
722
prop_Instance_shrinkMG inst =
723
  Instance.mem inst >= 2 * Types.unitMem ==>
724
    case Instance.shrinkByType inst Types.FailMem of
725
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
726
      _ -> False
727

    
728
prop_Instance_shrinkMF :: Instance.Instance -> Property
729
prop_Instance_shrinkMF inst =
730
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
731
    let inst' = inst { Instance.mem = mem}
732
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
733

    
734
prop_Instance_shrinkCG :: Instance.Instance -> Property
735
prop_Instance_shrinkCG inst =
736
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
737
    case Instance.shrinkByType inst Types.FailCPU of
738
      Types.Ok inst' ->
739
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
740
      _ -> False
741

    
742
prop_Instance_shrinkCF :: Instance.Instance -> Property
743
prop_Instance_shrinkCF inst =
744
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
745
    let inst' = inst { Instance.vcpus = vcpus }
746
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
747

    
748
prop_Instance_shrinkDG :: Instance.Instance -> Property
749
prop_Instance_shrinkDG inst =
750
  Instance.dsk inst >= 2 * Types.unitDsk ==>
751
    case Instance.shrinkByType inst Types.FailDisk of
752
      Types.Ok inst' ->
753
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
754
      _ -> False
755

    
756
prop_Instance_shrinkDF :: Instance.Instance -> Property
757
prop_Instance_shrinkDF inst =
758
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
759
    let inst' = inst { Instance.dsk = dsk }
760
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
761

    
762
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
763
prop_Instance_setMovable inst m =
764
  Instance.movable inst' ==? m
765
    where inst' = Instance.setMovable inst m
766

    
767
testSuite "Instance"
768
            [ 'prop_Instance_creat
769
            , 'prop_Instance_setIdx
770
            , 'prop_Instance_setName
771
            , 'prop_Instance_setAlias
772
            , 'prop_Instance_setPri
773
            , 'prop_Instance_setSec
774
            , 'prop_Instance_setBoth
775
            , 'prop_Instance_shrinkMG
776
            , 'prop_Instance_shrinkMF
777
            , 'prop_Instance_shrinkCG
778
            , 'prop_Instance_shrinkCF
779
            , 'prop_Instance_shrinkDG
780
            , 'prop_Instance_shrinkDF
781
            , 'prop_Instance_setMovable
782
            ]
783

    
784
-- ** Backends
785

    
786
-- *** Text backend tests
787

    
788
-- Instance text loader tests
789

    
790
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
791
                        -> NonEmptyList Char -> [Char]
792
                        -> NonNegative Int -> NonNegative Int -> Bool
793
                        -> Types.DiskTemplate -> Int -> Property
794
prop_Text_Load_Instance name mem dsk vcpus status
795
                        (NonEmpty pnode) snode
796
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
797
  pnode /= snode && pdx /= sdx ==>
798
  let vcpus_s = show vcpus
799
      dsk_s = show dsk
800
      mem_s = show mem
801
      su_s = show su
802
      status_s = Types.instanceStatusToRaw status
803
      ndx = if null snode
804
              then [(pnode, pdx)]
805
              else [(pnode, pdx), (snode, sdx)]
806
      nl = Map.fromList ndx
807
      tags = ""
808
      sbal = if autobal then "Y" else "N"
809
      sdt = Types.diskTemplateToRaw dt
810
      inst = Text.loadInst nl
811
             [name, mem_s, dsk_s, vcpus_s, status_s,
812
              sbal, pnode, snode, sdt, tags, su_s]
813
      fail1 = Text.loadInst nl
814
              [name, mem_s, dsk_s, vcpus_s, status_s,
815
               sbal, pnode, pnode, tags]
816
  in case inst of
817
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
818
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
819
                                        \ loading the instance" $
820
               Instance.name i == name &&
821
               Instance.vcpus i == vcpus &&
822
               Instance.mem i == mem &&
823
               Instance.pNode i == pdx &&
824
               Instance.sNode i == (if null snode
825
                                      then Node.noSecondary
826
                                      else sdx) &&
827
               Instance.autoBalance i == autobal &&
828
               Instance.spindleUse i == su &&
829
               Types.isBad fail1
830

    
831
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
832
prop_Text_Load_InstanceFail ktn fields =
833
  length fields /= 10 && length fields /= 11 ==>
834
    case Text.loadInst nl fields of
835
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
836
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
837
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
838
    where nl = Map.fromList ktn
839

    
840
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
841
                    -> Int -> Bool -> Bool
842
prop_Text_Load_Node name tm nm fm td fd tc fo =
843
  let conv v = if v < 0
844
                 then "?"
845
                 else show v
846
      tm_s = conv tm
847
      nm_s = conv nm
848
      fm_s = conv fm
849
      td_s = conv td
850
      fd_s = conv fd
851
      tc_s = conv tc
852
      fo_s = if fo
853
               then "Y"
854
               else "N"
855
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
856
      gid = Group.uuid defGroup
857
  in case Text.loadNode defGroupAssoc
858
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
859
       Nothing -> False
860
       Just (name', node) ->
861
         if fo || any_broken
862
           then Node.offline node
863
           else Node.name node == name' && name' == name &&
864
                Node.alias node == name &&
865
                Node.tMem node == fromIntegral tm &&
866
                Node.nMem node == nm &&
867
                Node.fMem node == fm &&
868
                Node.tDsk node == fromIntegral td &&
869
                Node.fDsk node == fd &&
870
                Node.tCpu node == fromIntegral tc
871

    
872
prop_Text_Load_NodeFail :: [String] -> Property
873
prop_Text_Load_NodeFail fields =
874
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
875

    
876
prop_Text_NodeLSIdempotent :: Property
877
prop_Text_NodeLSIdempotent =
878
  forAll (genNode (Just 1) Nothing) $ \node ->
879
  -- override failN1 to what loadNode returns by default
880
  let n = Node.setPolicy Types.defIPolicy $
881
          node { Node.failN1 = True, Node.offline = False }
882
  in
883
    (Text.loadNode defGroupAssoc.
884
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
885
    Just (Node.name n, n)
886

    
887
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
888
prop_Text_ISpecIdempotent ispec =
889
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
890
       Text.serializeISpec $ ispec of
891
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
892
    Types.Ok ispec' -> ispec ==? ispec'
893

    
894
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
895
prop_Text_IPolicyIdempotent ipol =
896
  case Text.loadIPolicy . Utils.sepSplit '|' $
897
       Text.serializeIPolicy owner ipol of
898
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
899
    Types.Ok res -> (owner, ipol) ==? res
900
  where owner = "dummy"
901

    
902
-- | This property, while being in the text tests, does more than just
903
-- test end-to-end the serialisation and loading back workflow; it
904
-- also tests the Loader.mergeData and the actuall
905
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
906
-- allocations, not for the business logic). As such, it's a quite
907
-- complex and slow test, and that's the reason we restrict it to
908
-- small cluster sizes.
909
prop_Text_CreateSerialise :: Property
910
prop_Text_CreateSerialise =
911
  forAll genTags $ \ctags ->
912
  forAll (choose (1, 20)) $ \maxiter ->
913
  forAll (choose (2, 10)) $ \count ->
914
  forAll genOnlineNode $ \node ->
915
  forAll (genInstanceSmallerThanNode node) $ \inst ->
916
  let nl = makeSmallCluster node count
917
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
918
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
919
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
920
     of
921
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
922
       Types.Ok (_, _, _, [], _) -> printTestCase
923
                                    "Failed to allocate: no allocations" False
924
       Types.Ok (_, nl', il', _, _) ->
925
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
926
                     Types.defIPolicy
927
             saved = Text.serializeCluster cdata
928
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
929
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
930
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
931
                ctags ==? ctags2 .&&.
932
                Types.defIPolicy ==? cpol2 .&&.
933
                il' ==? il2 .&&.
934
                defGroupList ==? gl2 .&&.
935
                nl' ==? nl2
936

    
937
testSuite "Text"
938
            [ 'prop_Text_Load_Instance
939
            , 'prop_Text_Load_InstanceFail
940
            , 'prop_Text_Load_Node
941
            , 'prop_Text_Load_NodeFail
942
            , 'prop_Text_NodeLSIdempotent
943
            , 'prop_Text_ISpecIdempotent
944
            , 'prop_Text_IPolicyIdempotent
945
            , 'prop_Text_CreateSerialise
946
            ]
947

    
948
-- *** Simu backend
949

    
950
-- | Generates a tuple of specs for simulation.
951
genSimuSpec :: Gen (String, Int, Int, Int, Int)
952
genSimuSpec = do
953
  pol <- elements [C.allocPolicyPreferred,
954
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
955
                  "p", "a", "u"]
956
 -- should be reasonable (nodes/group), bigger values only complicate
957
 -- the display of failed tests, and we don't care (in this particular
958
 -- test) about big node groups
959
  nodes <- choose (0, 20)
960
  dsk <- choose (0, maxDsk)
961
  mem <- choose (0, maxMem)
962
  cpu <- choose (0, maxCpu)
963
  return (pol, nodes, dsk, mem, cpu)
964

    
965
-- | Checks that given a set of corrects specs, we can load them
966
-- successfully, and that at high-level the values look right.
967
prop_Simu_Load :: Property
968
prop_Simu_Load =
969
  forAll (choose (0, 10)) $ \ngroups ->
970
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
971
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
972
                                          p n d m c::String) specs
973
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
974
      mdc_in = concatMap (\(_, n, d, m, c) ->
975
                            replicate n (fromIntegral m, fromIntegral d,
976
                                         fromIntegral c,
977
                                         fromIntegral m, fromIntegral d))
978
               specs :: [(Double, Double, Double, Int, Int)]
979
  in case Simu.parseData strspecs of
980
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
981
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
982
         let nodes = map snd $ IntMap.toAscList nl
983
             nidx = map Node.idx nodes
984
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
985
                                   Node.fMem n, Node.fDsk n)) nodes
986
         in
987
         Container.size gl ==? ngroups .&&.
988
         Container.size nl ==? totnodes .&&.
989
         Container.size il ==? 0 .&&.
990
         length tags ==? 0 .&&.
991
         ipol ==? Types.defIPolicy .&&.
992
         nidx ==? [1..totnodes] .&&.
993
         mdc_in ==? mdc_out .&&.
994
         map Group.iPolicy (Container.elems gl) ==?
995
             replicate ngroups Types.defIPolicy
996

    
997
testSuite "Simu"
998
            [ 'prop_Simu_Load
999
            ]
1000

    
1001
-- ** Node tests
1002

    
1003
prop_Node_setAlias :: Node.Node -> String -> Bool
1004
prop_Node_setAlias node name =
1005
  Node.name newnode == Node.name node &&
1006
  Node.alias newnode == name
1007
    where newnode = Node.setAlias node name
1008

    
1009
prop_Node_setOffline :: Node.Node -> Bool -> Property
1010
prop_Node_setOffline node status =
1011
  Node.offline newnode ==? status
1012
    where newnode = Node.setOffline node status
1013

    
1014
prop_Node_setXmem :: Node.Node -> Int -> Property
1015
prop_Node_setXmem node xm =
1016
  Node.xMem newnode ==? xm
1017
    where newnode = Node.setXmem node xm
1018

    
1019
prop_Node_setMcpu :: Node.Node -> Double -> Property
1020
prop_Node_setMcpu node mc =
1021
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1022
    where newnode = Node.setMcpu node mc
1023

    
1024
-- | Check that an instance add with too high memory or disk will be
1025
-- rejected.
1026
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1027
prop_Node_addPriFM node inst =
1028
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1029
  not (Instance.isOffline inst) ==>
1030
  case Node.addPri node inst'' of
1031
    Types.OpFail Types.FailMem -> True
1032
    _ -> False
1033
  where inst' = setInstanceSmallerThanNode node inst
1034
        inst'' = inst' { Instance.mem = Instance.mem inst }
1035

    
1036
-- | Check that adding a primary instance with too much disk fails
1037
-- with type FailDisk.
1038
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1039
prop_Node_addPriFD node inst =
1040
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1041
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1042
  let inst' = setInstanceSmallerThanNode node inst
1043
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1044
                     , Instance.diskTemplate = dt }
1045
  in case Node.addPri node inst'' of
1046
       Types.OpFail Types.FailDisk -> True
1047
       _ -> False
1048

    
1049
-- | Check that adding a primary instance with too many VCPUs fails
1050
-- with type FailCPU.
1051
prop_Node_addPriFC :: Property
1052
prop_Node_addPriFC =
1053
  forAll (choose (1, maxCpu)) $ \extra ->
1054
  forAll genOnlineNode $ \node ->
1055
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1056
  let inst' = setInstanceSmallerThanNode node inst
1057
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1058
  in case Node.addPri node inst'' of
1059
       Types.OpFail Types.FailCPU -> property True
1060
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1061

    
1062
-- | Check that an instance add with too high memory or disk will be
1063
-- rejected.
1064
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1065
prop_Node_addSec node inst pdx =
1066
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1067
    not (Instance.isOffline inst)) ||
1068
   Instance.dsk inst >= Node.fDsk node) &&
1069
  not (Node.failN1 node) ==>
1070
      isFailure (Node.addSec node inst pdx)
1071

    
1072
-- | Check that an offline instance with reasonable disk size but
1073
-- extra mem/cpu can always be added.
1074
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1075
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1076
  forAll genOnlineNode $ \node ->
1077
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1078
  let inst' = inst { Instance.runSt = Types.AdminOffline
1079
                   , Instance.mem = Node.availMem node + extra_mem
1080
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1081
  in case Node.addPri node inst' of
1082
       Types.OpGood _ -> property True
1083
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1084

    
1085
-- | Check that an offline instance with reasonable disk size but
1086
-- extra mem/cpu can always be added.
1087
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1088
                        -> Types.Ndx -> Property
1089
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1090
  forAll genOnlineNode $ \node ->
1091
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1092
  let inst' = inst { Instance.runSt = Types.AdminOffline
1093
                   , Instance.mem = Node.availMem node + extra_mem
1094
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1095
                   , Instance.diskTemplate = Types.DTDrbd8 }
1096
  in case Node.addSec node inst' pdx of
1097
       Types.OpGood _ -> property True
1098
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1099

    
1100
-- | Checks for memory reservation changes.
1101
prop_Node_rMem :: Instance.Instance -> Property
1102
prop_Node_rMem inst =
1103
  not (Instance.isOffline inst) ==>
1104
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1105
  -- ab = auto_balance, nb = non-auto_balance
1106
  -- we use -1 as the primary node of the instance
1107
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1108
                   , Instance.diskTemplate = Types.DTDrbd8 }
1109
      inst_ab = setInstanceSmallerThanNode node inst'
1110
      inst_nb = inst_ab { Instance.autoBalance = False }
1111
      -- now we have the two instances, identical except the
1112
      -- autoBalance attribute
1113
      orig_rmem = Node.rMem node
1114
      inst_idx = Instance.idx inst_ab
1115
      node_add_ab = Node.addSec node inst_ab (-1)
1116
      node_add_nb = Node.addSec node inst_nb (-1)
1117
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1118
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1119
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1120
       (Types.OpGood a_ab, Types.OpGood a_nb,
1121
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1122
         printTestCase "Consistency checks failed" $
1123
           Node.rMem a_ab >  orig_rmem &&
1124
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1125
           Node.rMem a_nb == orig_rmem &&
1126
           Node.rMem d_ab == orig_rmem &&
1127
           Node.rMem d_nb == orig_rmem &&
1128
           -- this is not related to rMem, but as good a place to
1129
           -- test as any
1130
           inst_idx `elem` Node.sList a_ab &&
1131
           inst_idx `notElem` Node.sList d_ab
1132
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1133

    
1134
-- | Check mdsk setting.
1135
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1136
prop_Node_setMdsk node mx =
1137
  Node.loDsk node' >= 0 &&
1138
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1139
  Node.availDisk node' >= 0 &&
1140
  Node.availDisk node' <= Node.fDsk node' &&
1141
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1142
  Node.mDsk node' == mx'
1143
    where node' = Node.setMdsk node mx'
1144
          SmallRatio mx' = mx
1145

    
1146
-- Check tag maps
1147
prop_Node_tagMaps_idempotent :: Property
1148
prop_Node_tagMaps_idempotent =
1149
  forAll genTags $ \tags ->
1150
  Node.delTags (Node.addTags m tags) tags ==? m
1151
    where m = Map.empty
1152

    
1153
prop_Node_tagMaps_reject :: Property
1154
prop_Node_tagMaps_reject =
1155
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1156
  let m = Node.addTags Map.empty tags
1157
  in all (\t -> Node.rejectAddTags m [t]) tags
1158

    
1159
prop_Node_showField :: Node.Node -> Property
1160
prop_Node_showField node =
1161
  forAll (elements Node.defaultFields) $ \ field ->
1162
  fst (Node.showHeader field) /= Types.unknownField &&
1163
  Node.showField node field /= Types.unknownField
1164

    
1165
prop_Node_computeGroups :: [Node.Node] -> Bool
1166
prop_Node_computeGroups nodes =
1167
  let ng = Node.computeGroups nodes
1168
      onlyuuid = map fst ng
1169
  in length nodes == sum (map (length . snd) ng) &&
1170
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1171
     length (nub onlyuuid) == length onlyuuid &&
1172
     (null nodes || not (null ng))
1173

    
1174
-- Check idempotence of add/remove operations
1175
prop_Node_addPri_idempotent :: Property
1176
prop_Node_addPri_idempotent =
1177
  forAll genOnlineNode $ \node ->
1178
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1179
  case Node.addPri node inst of
1180
    Types.OpGood node' -> Node.removePri node' inst ==? node
1181
    _ -> failTest "Can't add instance"
1182

    
1183
prop_Node_addSec_idempotent :: Property
1184
prop_Node_addSec_idempotent =
1185
  forAll genOnlineNode $ \node ->
1186
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1187
  let pdx = Node.idx node + 1
1188
      inst' = Instance.setPri inst pdx
1189
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1190
  in case Node.addSec node inst'' pdx of
1191
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1192
       _ -> failTest "Can't add instance"
1193

    
1194
testSuite "Node"
1195
            [ 'prop_Node_setAlias
1196
            , 'prop_Node_setOffline
1197
            , 'prop_Node_setMcpu
1198
            , 'prop_Node_setXmem
1199
            , 'prop_Node_addPriFM
1200
            , 'prop_Node_addPriFD
1201
            , 'prop_Node_addPriFC
1202
            , 'prop_Node_addSec
1203
            , 'prop_Node_addOfflinePri
1204
            , 'prop_Node_addOfflineSec
1205
            , 'prop_Node_rMem
1206
            , 'prop_Node_setMdsk
1207
            , 'prop_Node_tagMaps_idempotent
1208
            , 'prop_Node_tagMaps_reject
1209
            , 'prop_Node_showField
1210
            , 'prop_Node_computeGroups
1211
            , 'prop_Node_addPri_idempotent
1212
            , 'prop_Node_addSec_idempotent
1213
            ]
1214

    
1215
-- ** Cluster tests
1216

    
1217
-- | Check that the cluster score is close to zero for a homogeneous
1218
-- cluster.
1219
prop_Cluster_Score_Zero :: Node.Node -> Property
1220
prop_Cluster_Score_Zero node =
1221
  forAll (choose (1, 1024)) $ \count ->
1222
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1223
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1224
  let fn = Node.buildPeers node Container.empty
1225
      nlst = replicate count fn
1226
      score = Cluster.compCVNodes nlst
1227
  -- we can't say == 0 here as the floating point errors accumulate;
1228
  -- this should be much lower than the default score in CLI.hs
1229
  in score <= 1e-12
1230

    
1231
-- | Check that cluster stats are sane.
1232
prop_Cluster_CStats_sane :: Property
1233
prop_Cluster_CStats_sane =
1234
  forAll (choose (1, 1024)) $ \count ->
1235
  forAll genOnlineNode $ \node ->
1236
  let fn = Node.buildPeers node Container.empty
1237
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1238
      nl = Container.fromList nlst
1239
      cstats = Cluster.totalResources nl
1240
  in Cluster.csAdsk cstats >= 0 &&
1241
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1242

    
1243
-- | Check that one instance is allocated correctly, without
1244
-- rebalances needed.
1245
prop_Cluster_Alloc_sane :: Instance.Instance -> Property
1246
prop_Cluster_Alloc_sane inst =
1247
  forAll (choose (5, 20)) $ \count ->
1248
  forAll genOnlineNode $ \node ->
1249
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1250
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1251
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1252
     Cluster.tryAlloc nl il inst' of
1253
       Types.Bad _ -> False
1254
       Types.Ok as ->
1255
         case Cluster.asSolution as of
1256
           Nothing -> False
1257
           Just (xnl, xi, _, cv) ->
1258
             let il' = Container.add (Instance.idx xi) xi il
1259
                 tbl = Cluster.Table xnl il' cv []
1260
             in not (canBalance tbl True True False)
1261

    
1262
-- | Checks that on a 2-5 node cluster, we can allocate a random
1263
-- instance spec via tiered allocation (whatever the original instance
1264
-- spec), on either one or two nodes. Furthermore, we test that
1265
-- computed allocation statistics are correct.
1266
prop_Cluster_CanTieredAlloc :: Instance.Instance -> Property
1267
prop_Cluster_CanTieredAlloc inst =
1268
  forAll (choose (2, 5)) $ \count ->
1269
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1270
  let nl = makeSmallCluster node count
1271
      il = Container.empty
1272
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1273
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1274
  in case allocnodes >>= \allocnodes' ->
1275
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1276
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1277
       Types.Ok (_, nl', il', ixes, cstats) ->
1278
         let (ai_alloc, ai_pool, ai_unav) =
1279
               Cluster.computeAllocationDelta
1280
                (Cluster.totalResources nl)
1281
                (Cluster.totalResources nl')
1282
             all_nodes = Container.elems nl
1283
         in property (not (null ixes)) .&&.
1284
            IntMap.size il' ==? length ixes .&&.
1285
            length ixes ==? length cstats .&&.
1286
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1287
              sum (map Node.hiCpu all_nodes) .&&.
1288
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1289
              sum (map Node.tCpu all_nodes) .&&.
1290
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1291
              truncate (sum (map Node.tMem all_nodes)) .&&.
1292
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1293
              truncate (sum (map Node.tDsk all_nodes))
1294

    
1295
-- | Helper function to create a cluster with the given range of nodes
1296
-- and allocate an instance on it.
1297
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1298
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1299
genClusterAlloc count node inst =
1300
  let nl = makeSmallCluster node count
1301
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1302
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1303
     Cluster.tryAlloc nl Container.empty inst of
1304
       Types.Bad _ -> Types.Bad "Can't allocate"
1305
       Types.Ok as ->
1306
         case Cluster.asSolution as of
1307
           Nothing -> Types.Bad "Empty solution?"
1308
           Just (xnl, xi, _, _) ->
1309
             let xil = Container.add (Instance.idx xi) xi Container.empty
1310
             in Types.Ok (xnl, xil, xi)
1311

    
1312
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1313
-- we can also relocate it.
1314
prop_Cluster_AllocRelocate :: Property
1315
prop_Cluster_AllocRelocate =
1316
  forAll (choose (4, 8)) $ \count ->
1317
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1318
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1319
  case genClusterAlloc count node inst of
1320
    Types.Bad msg -> failTest msg
1321
    Types.Ok (nl, il, inst') ->
1322
      case IAlloc.processRelocate defGroupList nl il
1323
             (Instance.idx inst) 1
1324
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1325
                 then Instance.sNode
1326
                 else Instance.pNode) inst'] of
1327
        Types.Ok _ -> property True
1328
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1329

    
1330
-- | Helper property checker for the result of a nodeEvac or
1331
-- changeGroup operation.
1332
check_EvacMode :: Group.Group -> Instance.Instance
1333
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1334
               -> Property
1335
check_EvacMode grp inst result =
1336
  case result of
1337
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1338
    Types.Ok (_, _, es) ->
1339
      let moved = Cluster.esMoved es
1340
          failed = Cluster.esFailed es
1341
          opcodes = not . null $ Cluster.esOpCodes es
1342
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1343
         failmsg "'opcodes' is null" opcodes .&&.
1344
         case moved of
1345
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1346
                               .&&.
1347
                               failmsg "wrong target group"
1348
                                         (gdx == Group.idx grp)
1349
           v -> failmsg  ("invalid solution: " ++ show v) False
1350
  where failmsg :: String -> Bool -> Property
1351
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1352
        idx = Instance.idx inst
1353

    
1354
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1355
-- we can also node-evacuate it.
1356
prop_Cluster_AllocEvacuate :: Property
1357
prop_Cluster_AllocEvacuate =
1358
  forAll (choose (4, 8)) $ \count ->
1359
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1360
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1361
  case genClusterAlloc count node inst of
1362
    Types.Bad msg -> failTest msg
1363
    Types.Ok (nl, il, inst') ->
1364
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
1365
                              Cluster.tryNodeEvac defGroupList nl il mode
1366
                                [Instance.idx inst']) .
1367
                              evacModeOptions .
1368
                              Instance.mirrorType $ inst'
1369

    
1370
-- | Checks that on a 4-8 node cluster with two node groups, once we
1371
-- allocate an instance on the first node group, we can also change
1372
-- its group.
1373
prop_Cluster_AllocChangeGroup :: Property
1374
prop_Cluster_AllocChangeGroup =
1375
  forAll (choose (4, 8)) $ \count ->
1376
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1377
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1378
  case genClusterAlloc count node inst of
1379
    Types.Bad msg -> failTest msg
1380
    Types.Ok (nl, il, inst') ->
1381
      -- we need to add a second node group and nodes to the cluster
1382
      let nl2 = Container.elems $ makeSmallCluster node count
1383
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1384
          maxndx = maximum . map Node.idx $ nl2
1385
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1386
                             , Node.idx = Node.idx n + maxndx }) nl2
1387
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1388
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1389
          nl' = IntMap.union nl nl4
1390
      in check_EvacMode grp2 inst' $
1391
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1392

    
1393
-- | Check that allocating multiple instances on a cluster, then
1394
-- adding an empty node, results in a valid rebalance.
1395
prop_Cluster_AllocBalance :: Property
1396
prop_Cluster_AllocBalance =
1397
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1398
  forAll (choose (3, 5)) $ \count ->
1399
  not (Node.offline node) && not (Node.failN1 node) ==>
1400
  let nl = makeSmallCluster node count
1401
      (hnode, nl') = IntMap.deleteFindMax nl
1402
      il = Container.empty
1403
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1404
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1405
  in case allocnodes >>= \allocnodes' ->
1406
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1407
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1408
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1409
       Types.Ok (_, xnl, il', _, _) ->
1410
         let ynl = Container.add (Node.idx hnode) hnode xnl
1411
             cv = Cluster.compCV ynl
1412
             tbl = Cluster.Table ynl il' cv []
1413
         in printTestCase "Failed to rebalance" $
1414
            canBalance tbl True True False
1415

    
1416
-- | Checks consistency.
1417
prop_Cluster_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
1418
prop_Cluster_CheckConsistency node inst =
1419
  let nl = makeSmallCluster node 3
1420
      [node1, node2, node3] = Container.elems nl
1421
      node3' = node3 { Node.group = 1 }
1422
      nl' = Container.add (Node.idx node3') node3' nl
1423
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1424
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1425
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1426
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1427
  in null (ccheck [(0, inst1)]) &&
1428
     null (ccheck [(0, inst2)]) &&
1429
     (not . null $ ccheck [(0, inst3)])
1430

    
1431
-- | For now, we only test that we don't lose instances during the split.
1432
prop_Cluster_SplitCluster :: Node.Node -> Instance.Instance -> Property
1433
prop_Cluster_SplitCluster node inst =
1434
  forAll (choose (0, 100)) $ \icnt ->
1435
  let nl = makeSmallCluster node 2
1436
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1437
                   (nl, Container.empty) [1..icnt]
1438
      gni = Cluster.splitCluster nl' il'
1439
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1440
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1441
                                 (Container.elems nl'')) gni
1442

    
1443
-- | Helper function to check if we can allocate an instance on a
1444
-- given node list.
1445
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1446
canAllocOn nl reqnodes inst =
1447
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1448
       Cluster.tryAlloc nl (Container.empty) inst of
1449
       Types.Bad _ -> False
1450
       Types.Ok as ->
1451
         case Cluster.asSolution as of
1452
           Nothing -> False
1453
           Just _ -> True
1454

    
1455
-- | Checks that allocation obeys minimum and maximum instance
1456
-- policies. The unittest generates a random node, duplicates it /count/
1457
-- times, and generates a random instance that can be allocated on
1458
-- this mini-cluster; it then checks that after applying a policy that
1459
-- the instance doesn't fits, the allocation fails.
1460
prop_Cluster_AllocPolicy :: Node.Node -> Property
1461
prop_Cluster_AllocPolicy node =
1462
  -- rqn is the required nodes (1 or 2)
1463
  forAll (choose (1, 2)) $ \rqn ->
1464
  forAll (choose (5, 20)) $ \count ->
1465
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1466
         $ \inst ->
1467
  forAll (arbitrary `suchThat` (isFailure .
1468
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1469
  let node' = Node.setPolicy ipol node
1470
      nl = makeSmallCluster node' count
1471
  in not $ canAllocOn nl rqn inst
1472

    
1473
testSuite "Cluster"
1474
            [ 'prop_Cluster_Score_Zero
1475
            , 'prop_Cluster_CStats_sane
1476
            , 'prop_Cluster_Alloc_sane
1477
            , 'prop_Cluster_CanTieredAlloc
1478
            , 'prop_Cluster_AllocRelocate
1479
            , 'prop_Cluster_AllocEvacuate
1480
            , 'prop_Cluster_AllocChangeGroup
1481
            , 'prop_Cluster_AllocBalance
1482
            , 'prop_Cluster_CheckConsistency
1483
            , 'prop_Cluster_SplitCluster
1484
            , 'prop_Cluster_AllocPolicy
1485
            ]
1486

    
1487
-- ** OpCodes tests
1488

    
1489
-- | Check that opcode serialization is idempotent.
1490
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1491
prop_OpCodes_serialization op =
1492
  case J.readJSON (J.showJSON op) of
1493
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1494
    J.Ok op' -> op ==? op'
1495

    
1496
-- | Check that Python and Haskell defined the same opcode list.
1497
case_OpCodes_AllDefined :: HUnit.Assertion
1498
case_OpCodes_AllDefined = do
1499
  py_stdout <- runPython "from ganeti import opcodes\n\
1500
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
1501
               checkPythonResult
1502
  let py_ops = sort $ lines py_stdout
1503
      hs_ops = OpCodes.allOpIDs
1504
      -- extra_py = py_ops \\ hs_ops
1505
      extra_hs = hs_ops \\ py_ops
1506
  -- FIXME: uncomment when we have parity
1507
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
1508
  --                  unlines extra_py) (null extra_py)
1509
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
1510
                    unlines extra_hs) (null extra_hs)
1511

    
1512
-- | Custom HUnit test case that forks a Python process and checks
1513
-- correspondence between Haskell-generated OpCodes and their Python
1514
-- decoded, validated and re-encoded version.
1515
--
1516
-- Note that we have a strange beast here: since launching Python is
1517
-- expensive, we don't do this via a usual QuickProperty, since that's
1518
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
1519
-- single HUnit assertion, and in it we manually use QuickCheck to
1520
-- generate 500 opcodes times the number of defined opcodes, which
1521
-- then we pass in bulk to Python. The drawbacks to this method are
1522
-- two fold: we cannot control the number of generated opcodes, since
1523
-- HUnit assertions don't get access to the test options, and for the
1524
-- same reason we can't run a repeatable seed. We should probably find
1525
-- a better way to do this, for example by having a
1526
-- separately-launched Python process (if not running the tests would
1527
-- be skipped).
1528
case_OpCodes_py_compat :: HUnit.Assertion
1529
case_OpCodes_py_compat = do
1530
  let num_opcodes = length OpCodes.allOpIDs * 500
1531
  sample_opcodes <- sample' (vectorOf num_opcodes
1532
                             (arbitrary::Gen OpCodes.OpCode))
1533
  let opcodes = head sample_opcodes
1534
      serialized = J.encode opcodes
1535
  py_stdout <-
1536
     runPython "from ganeti import opcodes\n\
1537
               \import sys\n\
1538
               \from ganeti import serializer\n\
1539
               \op_data = serializer.Load(sys.stdin.read())\n\
1540
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
1541
               \for op in decoded:\n\
1542
               \  op.Validate(True)\n\
1543
               \encoded = [op.__getstate__() for op in decoded]\n\
1544
               \print serializer.Dump(encoded)" serialized
1545
     >>= checkPythonResult
1546
  let deserialised = (J.decode py_stdout::J.Result [OpCodes.OpCode])
1547
  decoded <- case deserialised of
1548
               J.Ok ops -> return ops
1549
               J.Error msg ->
1550
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
1551
                 -- this already raised an expection, but we need it
1552
                 -- for proper types
1553
                 >> fail "Unable to decode opcodes"
1554
  HUnit.assertEqual "Mismatch in number of returned opcodes"
1555
    (length opcodes) (length decoded)
1556
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
1557
        ) $ zip opcodes decoded
1558

    
1559
testSuite "OpCodes"
1560
            [ 'prop_OpCodes_serialization
1561
            , 'case_OpCodes_AllDefined
1562
            , 'case_OpCodes_py_compat
1563
            ]
1564

    
1565
-- ** Jobs tests
1566

    
1567
-- | Check that (queued) job\/opcode status serialization is idempotent.
1568
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
1569
prop_Jobs_OpStatus_serialization os =
1570
  case J.readJSON (J.showJSON os) of
1571
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1572
    J.Ok os' -> os ==? os'
1573

    
1574
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
1575
prop_Jobs_JobStatus_serialization js =
1576
  case J.readJSON (J.showJSON js) of
1577
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1578
    J.Ok js' -> js ==? js'
1579

    
1580
testSuite "Jobs"
1581
            [ 'prop_Jobs_OpStatus_serialization
1582
            , 'prop_Jobs_JobStatus_serialization
1583
            ]
1584

    
1585
-- ** Loader tests
1586

    
1587
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1588
prop_Loader_lookupNode ktn inst node =
1589
  Loader.lookupNode nl inst node ==? Map.lookup node nl
1590
    where nl = Map.fromList ktn
1591

    
1592
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1593
prop_Loader_lookupInstance kti inst =
1594
  Loader.lookupInstance il inst ==? Map.lookup inst il
1595
    where il = Map.fromList kti
1596

    
1597
prop_Loader_assignIndices :: Property
1598
prop_Loader_assignIndices =
1599
  -- generate nodes with unique names
1600
  forAll (arbitrary `suchThat`
1601
          (\nodes ->
1602
             let names = map Node.name nodes
1603
             in length names == length (nub names))) $ \nodes ->
1604
  let (nassoc, kt) =
1605
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1606
  in Map.size nassoc == length nodes &&
1607
     Container.size kt == length nodes &&
1608
     if not (null nodes)
1609
       then maximum (IntMap.keys kt) == length nodes - 1
1610
       else True
1611

    
1612
-- | Checks that the number of primary instances recorded on the nodes
1613
-- is zero.
1614
prop_Loader_mergeData :: [Node.Node] -> Bool
1615
prop_Loader_mergeData ns =
1616
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1617
  in case Loader.mergeData [] [] [] []
1618
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1619
    Types.Bad _ -> False
1620
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1621
      let nodes = Container.elems nl
1622
          instances = Container.elems il
1623
      in (sum . map (length . Node.pList)) nodes == 0 &&
1624
         null instances
1625

    
1626
-- | Check that compareNameComponent on equal strings works.
1627
prop_Loader_compareNameComponent_equal :: String -> Bool
1628
prop_Loader_compareNameComponent_equal s =
1629
  BasicTypes.compareNameComponent s s ==
1630
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1631

    
1632
-- | Check that compareNameComponent on prefix strings works.
1633
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1634
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1635
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1636
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1637

    
1638
testSuite "Loader"
1639
            [ 'prop_Loader_lookupNode
1640
            , 'prop_Loader_lookupInstance
1641
            , 'prop_Loader_assignIndices
1642
            , 'prop_Loader_mergeData
1643
            , 'prop_Loader_compareNameComponent_equal
1644
            , 'prop_Loader_compareNameComponent_prefix
1645
            ]
1646

    
1647
-- ** Types tests
1648

    
1649
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1650
prop_Types_AllocPolicy_serialisation apol =
1651
  case J.readJSON (J.showJSON apol) of
1652
    J.Ok p -> p ==? apol
1653
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1654

    
1655
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1656
prop_Types_DiskTemplate_serialisation dt =
1657
  case J.readJSON (J.showJSON dt) of
1658
    J.Ok p -> p ==? dt
1659
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1660

    
1661
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1662
prop_Types_ISpec_serialisation ispec =
1663
  case J.readJSON (J.showJSON ispec) of
1664
    J.Ok p -> p ==? ispec
1665
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1666

    
1667
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1668
prop_Types_IPolicy_serialisation ipol =
1669
  case J.readJSON (J.showJSON ipol) of
1670
    J.Ok p -> p ==? ipol
1671
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1672

    
1673
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1674
prop_Types_EvacMode_serialisation em =
1675
  case J.readJSON (J.showJSON em) of
1676
    J.Ok p -> p ==? em
1677
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1678

    
1679
prop_Types_opToResult :: Types.OpResult Int -> Bool
1680
prop_Types_opToResult op =
1681
  case op of
1682
    Types.OpFail _ -> Types.isBad r
1683
    Types.OpGood v -> case r of
1684
                        Types.Bad _ -> False
1685
                        Types.Ok v' -> v == v'
1686
  where r = Types.opToResult op
1687

    
1688
prop_Types_eitherToResult :: Either String Int -> Bool
1689
prop_Types_eitherToResult ei =
1690
  case ei of
1691
    Left _ -> Types.isBad r
1692
    Right v -> case r of
1693
                 Types.Bad _ -> False
1694
                 Types.Ok v' -> v == v'
1695
    where r = Types.eitherToResult ei
1696

    
1697
testSuite "Types"
1698
            [ 'prop_Types_AllocPolicy_serialisation
1699
            , 'prop_Types_DiskTemplate_serialisation
1700
            , 'prop_Types_ISpec_serialisation
1701
            , 'prop_Types_IPolicy_serialisation
1702
            , 'prop_Types_EvacMode_serialisation
1703
            , 'prop_Types_opToResult
1704
            , 'prop_Types_eitherToResult
1705
            ]
1706

    
1707
-- ** CLI tests
1708

    
1709
-- | Test correct parsing.
1710
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1711
prop_CLI_parseISpec descr dsk mem cpu =
1712
  let str = printf "%d,%d,%d" dsk mem cpu::String
1713
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1714

    
1715
-- | Test parsing failure due to wrong section count.
1716
prop_CLI_parseISpecFail :: String -> Property
1717
prop_CLI_parseISpecFail descr =
1718
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1719
  forAll (replicateM nelems arbitrary) $ \values ->
1720
  let str = intercalate "," $ map show (values::[Int])
1721
  in case CLI.parseISpecString descr str of
1722
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1723
       _ -> property True
1724

    
1725
-- | Test parseYesNo.
1726
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1727
prop_CLI_parseYesNo def testval val =
1728
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1729
  if testval
1730
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1731
    else let result = CLI.parseYesNo def (Just actual_val)
1732
         in if actual_val `elem` ["yes", "no"]
1733
              then result ==? Types.Ok (actual_val == "yes")
1734
              else property $ Types.isBad result
1735

    
1736
-- | Helper to check for correct parsing of string arg.
1737
checkStringArg :: [Char]
1738
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1739
                   CLI.Options -> Maybe [Char])
1740
               -> Property
1741
checkStringArg val (opt, fn) =
1742
  let GetOpt.Option _ longs _ _ = opt
1743
  in case longs of
1744
       [] -> failTest "no long options?"
1745
       cmdarg:_ ->
1746
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1747
           Left e -> failTest $ "Failed to parse option: " ++ show e
1748
           Right (options, _) -> fn options ==? Just val
1749

    
1750
-- | Test a few string arguments.
1751
prop_CLI_StringArg :: [Char] -> Property
1752
prop_CLI_StringArg argument =
1753
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1754
             , (CLI.oDynuFile,      CLI.optDynuFile)
1755
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1756
             , (CLI.oReplay,        CLI.optReplay)
1757
             , (CLI.oPrintCommands, CLI.optShowCmds)
1758
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1759
             ]
1760
  in conjoin $ map (checkStringArg argument) args
1761

    
1762
-- | Helper to test that a given option is accepted OK with quick exit.
1763
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1764
checkEarlyExit name options param =
1765
  case CLI.parseOptsInner [param] name options of
1766
    Left (code, _) -> if code == 0
1767
                          then property True
1768
                          else failTest $ "Program " ++ name ++
1769
                                 " returns invalid code " ++ show code ++
1770
                                 " for option " ++ param
1771
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1772
         param ++ " as early exit one"
1773

    
1774
-- | Test that all binaries support some common options. There is
1775
-- nothing actually random about this test...
1776
prop_CLI_stdopts :: Property
1777
prop_CLI_stdopts =
1778
  let params = ["-h", "--help", "-V", "--version"]
1779
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1780
      -- apply checkEarlyExit across the cartesian product of params and opts
1781
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1782

    
1783
testSuite "CLI"
1784
          [ 'prop_CLI_parseISpec
1785
          , 'prop_CLI_parseISpecFail
1786
          , 'prop_CLI_parseYesNo
1787
          , 'prop_CLI_StringArg
1788
          , 'prop_CLI_stdopts
1789
          ]
1790

    
1791
-- * JSON tests
1792

    
1793
prop_JSON_toArray :: [Int] -> Property
1794
prop_JSON_toArray intarr =
1795
  let arr = map J.showJSON intarr in
1796
  case JSON.toArray (J.JSArray arr) of
1797
    Types.Ok arr' -> arr ==? arr'
1798
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1799

    
1800
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1801
prop_JSON_toArrayFail i s b =
1802
  -- poor man's instance Arbitrary JSValue
1803
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1804
  case JSON.toArray item of
1805
    Types.Bad _ -> property True
1806
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1807

    
1808
testSuite "JSON"
1809
          [ 'prop_JSON_toArray
1810
          , 'prop_JSON_toArrayFail
1811
          ]
1812

    
1813
-- * Luxi tests
1814

    
1815
instance Arbitrary Luxi.TagObject where
1816
  arbitrary = elements [minBound..maxBound]
1817

    
1818
instance Arbitrary Luxi.LuxiReq where
1819
  arbitrary = elements [minBound..maxBound]
1820

    
1821
instance Arbitrary Luxi.LuxiOp where
1822
  arbitrary = do
1823
    lreq <- arbitrary
1824
    case lreq of
1825
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
1826
      Luxi.ReqQueryFields -> Luxi.QueryFields <$> arbitrary <*> getFields
1827
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1828
                            getFields <*> arbitrary
1829
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1830
                             arbitrary <*> arbitrary
1831
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1832
                                getFields <*> arbitrary
1833
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1834
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1835
                              (listOf getFQDN) <*> arbitrary
1836
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1837
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1838
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary <*> getFQDN
1839
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1840
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1841
                                (resize maxOpCodes arbitrary)
1842
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1843
                                  getFields <*> pure J.JSNull <*>
1844
                                  pure J.JSNull <*> arbitrary
1845
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1846
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1847
                                 arbitrary
1848
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1849
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1850
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1851

    
1852
-- | Simple check that encoding/decoding of LuxiOp works.
1853
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1854
prop_Luxi_CallEncoding op =
1855
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1856

    
1857
-- | Helper to a get a temporary file name.
1858
getTempFileName :: IO FilePath
1859
getTempFileName = do
1860
  tempdir <- getTemporaryDirectory
1861
  (fpath, handle) <- openTempFile tempdir "luxitest"
1862
  _ <- hClose handle
1863
  removeFile fpath
1864
  return fpath
1865

    
1866
-- | Server ping-pong helper.
1867
luxiServerPong :: Luxi.Client -> IO ()
1868
luxiServerPong c = do
1869
  msg <- Luxi.recvMsgExt c
1870
  case msg of
1871
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
1872
    _ -> return ()
1873

    
1874
-- | Client ping-pong helper.
1875
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1876
luxiClientPong c =
1877
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1878

    
1879
-- | Monadic check that, given a server socket, we can connect via a
1880
-- client to it, and that we can send a list of arbitrary messages and
1881
-- get back what we sent.
1882
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1883
prop_Luxi_ClientServer dnschars = monadicIO $ do
1884
  let msgs = map (map dnsGetChar) dnschars
1885
  fpath <- run $ getTempFileName
1886
  -- we need to create the server first, otherwise (if we do it in the
1887
  -- forked thread) the client could try to connect to it before it's
1888
  -- ready
1889
  server <- run $ Luxi.getServer fpath
1890
  -- fork the server responder
1891
  _ <- run . forkIO $
1892
    bracket
1893
      (Luxi.acceptClient server)
1894
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
1895
      luxiServerPong
1896
  replies <- run $
1897
    bracket
1898
      (Luxi.getClient fpath)
1899
      Luxi.closeClient
1900
      (\c -> luxiClientPong c msgs)
1901
  assert $ replies == msgs
1902

    
1903
testSuite "Luxi"
1904
          [ 'prop_Luxi_CallEncoding
1905
          , 'prop_Luxi_ClientServer
1906
          ]
1907

    
1908
-- * Ssconf tests
1909

    
1910
instance Arbitrary Ssconf.SSKey where
1911
  arbitrary = elements [minBound..maxBound]
1912

    
1913
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1914
prop_Ssconf_filename key =
1915
  printTestCase "Key doesn't start with correct prefix" $
1916
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1917

    
1918
testSuite "Ssconf"
1919
  [ 'prop_Ssconf_filename
1920
  ]
1921

    
1922
-- * Qlang tests
1923

    
1924
-- | Tests that serialisation/deserialisation of filters is
1925
-- idempotent.
1926
prop_Qlang_Serialisation :: Property
1927
prop_Qlang_Serialisation =
1928
  forAll genFilter $ \flt ->
1929
  J.readJSON (J.showJSON flt) ==? J.Ok flt
1930

    
1931
prop_Qlang_FilterRegex_instances :: Qlang.FilterRegex -> Property
1932
prop_Qlang_FilterRegex_instances rex =
1933
  printTestCase "failed JSON encoding"
1934
    (J.readJSON (J.showJSON rex) ==? J.Ok rex) .&&.
1935
  printTestCase "failed read/show instances" (read (show rex) ==? rex)
1936

    
1937
testSuite "Qlang"
1938
  [ 'prop_Qlang_Serialisation
1939
  , 'prop_Qlang_FilterRegex_instances
1940
  ]