Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ a9c3ba29

History | View | Annotate | Download (14.3 kB)

1
{-| Unittest helpers for ganeti-htools.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
8

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

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Test.Ganeti.TestCommon
27
  ( maxMem
28
  , maxDsk
29
  , maxCpu
30
  , maxSpindles
31
  , maxVcpuRatio
32
  , maxSpindleRatio
33
  , maxNodes
34
  , maxOpCodes
35
  , (==?)
36
  , (/=?)
37
  , failTest
38
  , passTest
39
  , pythonCmd
40
  , runPython
41
  , checkPythonResult
42
  , DNSChar(..)
43
  , genName
44
  , genFQDN
45
  , genUUID
46
  , genMaybe
47
  , genTags
48
  , genFields
49
  , genUniquesList
50
  , SmallRatio(..)
51
  , genSetHelper
52
  , genSet
53
  , genListSet
54
  , genAndRestArguments
55
  , genIPv4Address
56
  , genIPv4Network
57
  , genIp6Addr
58
  , genIp6Net
59
  , genOpCodesTagName
60
  , genLuxiTagName
61
  , netmask2NumHosts
62
  , testSerialisation
63
  , testDeserialisationFail
64
  , resultProp
65
  , readTestData
66
  , genSample
67
  , testParser
68
  , genPropParser
69
  , genNonNegative
70
  , relativeError
71
  , getTempFileName
72
  ) where
73

    
74
import Control.Applicative
75
import Control.Exception (catchJust)
76
import Control.Monad
77
import Data.Attoparsec.Text (Parser, parseOnly)
78
import Data.List
79
import qualified Data.Map as M
80
import Data.Text (pack)
81
import Data.Word
82
import qualified Data.Set as Set
83
import System.Directory (getTemporaryDirectory, removeFile)
84
import System.Environment (getEnv)
85
import System.Exit (ExitCode(..))
86
import System.IO (hClose, openTempFile)
87
import System.IO.Error (isDoesNotExistError)
88
import System.Process (readProcessWithExitCode)
89
import qualified Test.HUnit as HUnit
90
import Test.QuickCheck
91
import Test.QuickCheck.Monadic
92
import qualified Text.JSON as J
93
import Numeric
94

    
95
import qualified Ganeti.BasicTypes as BasicTypes
96
import Ganeti.Types
97

    
98
-- * Constants
99

    
100
-- | Maximum memory (1TiB, somewhat random value).
101
maxMem :: Int
102
maxMem = 1024 * 1024
103

    
104
-- | Maximum disk (8TiB, somewhat random value).
105
maxDsk :: Int
106
maxDsk = 1024 * 1024 * 8
107

    
108
-- | Max CPUs (1024, somewhat random value).
109
maxCpu :: Int
110
maxCpu = 1024
111

    
112
-- | Max spindles (1024, somewhat random value).
113
maxSpindles :: Int
114
maxSpindles = 1024
115

    
116
-- | Max vcpu ratio (random value).
117
maxVcpuRatio :: Double
118
maxVcpuRatio = 1024.0
119

    
120
-- | Max spindle ratio (random value).
121
maxSpindleRatio :: Double
122
maxSpindleRatio = 1024.0
123

    
124
-- | Max nodes, used just to limit arbitrary instances for smaller
125
-- opcode definitions (e.g. list of nodes in OpTestDelay).
126
maxNodes :: Int
127
maxNodes = 32
128

    
129
-- | Max opcodes or jobs in a submit job and submit many jobs.
130
maxOpCodes :: Int
131
maxOpCodes = 16
132

    
133
-- * Helper functions
134

    
135
-- | Checks for equality with proper annotation. The first argument is
136
-- the computed value, the second one the expected value.
137
(==?) :: (Show a, Eq a) => a -> a -> Property
138
(==?) x y = printTestCase
139
            ("Expected equality, but got mismatch\nexpected: " ++
140
             show y ++ "\n but got: " ++ show x) (x == y)
141
infix 3 ==?
142

    
143
-- | Checks for inequality with proper annotation. The first argument
144
-- is the computed value, the second one the expected (not equal)
145
-- value.
146
(/=?) :: (Show a, Eq a) => a -> a -> Property
147
(/=?) x y = printTestCase
148
            ("Expected inequality, but got equality: '" ++
149
             show x ++ "'.") (x /= y)
150
infix 3 /=?
151

    
152
-- | Show a message and fail the test.
153
failTest :: String -> Property
154
failTest msg = printTestCase msg False
155

    
156
-- | A 'True' property.
157
passTest :: Property
158
passTest = property True
159

    
160
-- | Return the python binary to use. If the PYTHON environment
161
-- variable is defined, use its value, otherwise use just \"python\".
162
pythonCmd :: IO String
163
pythonCmd = catchJust (guard . isDoesNotExistError)
164
            (getEnv "PYTHON") (const (return "python"))
165

    
166
-- | Run Python with an expression, returning the exit code, standard
167
-- output and error.
168
runPython :: String -> String -> IO (ExitCode, String, String)
169
runPython expr stdin = do
170
  py_binary <- pythonCmd
171
  readProcessWithExitCode py_binary ["-c", expr] stdin
172

    
173
-- | Check python exit code, and fail via HUnit assertions if
174
-- non-zero. Otherwise, return the standard output.
175
checkPythonResult :: (ExitCode, String, String) -> IO String
176
checkPythonResult (py_code, py_stdout, py_stderr) = do
177
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
178
       ExitSuccess py_code
179
  return py_stdout
180

    
181
-- * Arbitrary instances
182

    
183
-- | Defines a DNS name.
184
newtype DNSChar = DNSChar { dnsGetChar::Char }
185

    
186
instance Arbitrary DNSChar where
187
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
188

    
189
instance Show DNSChar where
190
  show = show . dnsGetChar
191

    
192
-- | Generates a single name component.
193
genName :: Gen String
194
genName = do
195
  n <- choose (1, 16)
196
  dn <- vector n
197
  return (map dnsGetChar dn)
198

    
199
-- | Generates an entire FQDN.
200
genFQDN :: Gen String
201
genFQDN = do
202
  ncomps <- choose (1, 4)
203
  names <- vectorOf ncomps genName
204
  return $ intercalate "." names
205

    
206
-- | Generates a UUID-like string.
207
--
208
-- Only to be used for QuickCheck testing. For obtaining actual UUIDs use
209
-- the newUUID function in Ganeti.Utils
210
genUUID :: Gen String
211
genUUID = do
212
  c1 <- vector 6
213
  c2 <- vector 4
214
  c3 <- vector 4
215
  c4 <- vector 4
216
  c5 <- vector 4
217
  c6 <- vector 4
218
  c7 <- vector 6
219
  return $ map dnsGetChar c1 ++ "-" ++ map dnsGetChar c2 ++ "-" ++
220
    map dnsGetChar c3 ++ "-" ++ map dnsGetChar c4 ++ "-" ++
221
    map dnsGetChar c5 ++ "-" ++ map dnsGetChar c6 ++ "-" ++
222
    map dnsGetChar c7
223

    
224
-- | Combinator that generates a 'Maybe' using a sub-combinator.
225
genMaybe :: Gen a -> Gen (Maybe a)
226
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
227

    
228
-- | Defines a tag type.
229
newtype TagChar = TagChar { tagGetChar :: Char }
230

    
231
-- | All valid tag chars. This doesn't need to match _exactly_
232
-- Ganeti's own tag regex, just enough for it to be close.
233
tagChar :: String
234
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
235

    
236
instance Arbitrary TagChar where
237
  arbitrary = liftM TagChar $ elements tagChar
238

    
239
-- | Generates a tag
240
genTag :: Gen [TagChar]
241
genTag = do
242
  -- the correct value would be C.maxTagLen, but that's way too
243
  -- verbose in unittests, and at the moment I don't see any possible
244
  -- bugs with longer tags and the way we use tags in htools
245
  n <- choose (1, 10)
246
  vector n
247

    
248
-- | Generates a list of tags (correctly upper bounded).
249
genTags :: Gen [String]
250
genTags = do
251
  -- the correct value would be C.maxTagsPerObj, but per the comment
252
  -- in genTag, we don't use tags enough in htools to warrant testing
253
  -- such big values
254
  n <- choose (0, 10::Int)
255
  tags <- mapM (const genTag) [1..n]
256
  return $ map (map tagGetChar) tags
257

    
258
-- | Generates a fields list. This uses the same character set as a
259
-- DNS name (just for simplicity).
260
genFields :: Gen [String]
261
genFields = do
262
  n <- choose (1, 32)
263
  vectorOf n genName
264

    
265
-- | Generates a list of a given size with non-duplicate elements.
266
genUniquesList :: (Eq a, Arbitrary a, Ord a) => Int -> Gen a -> Gen [a]
267
genUniquesList cnt generator = do
268
  set <- foldM (\set _ -> do
269
                  newelem <- generator `suchThat` (`Set.notMember` set)
270
                  return (Set.insert newelem set)) Set.empty [1..cnt]
271
  return $ Set.toList set
272

    
273
newtype SmallRatio = SmallRatio Double deriving Show
274
instance Arbitrary SmallRatio where
275
  arbitrary = liftM SmallRatio $ choose (0, 1)
276

    
277
-- | Helper for 'genSet', declared separately due to type constraints.
278
genSetHelper :: (Ord a) => [a] -> Maybe Int -> Gen (Set.Set a)
279
genSetHelper candidates size = do
280
  size' <- case size of
281
             Nothing -> choose (0, length candidates)
282
             Just s | s > length candidates ->
283
                        error $ "Invalid size " ++ show s ++ ", maximum is " ++
284
                                show (length candidates)
285
                    | otherwise -> return s
286
  foldM (\set _ -> do
287
           newelem <- elements candidates `suchThat` (`Set.notMember` set)
288
           return (Set.insert newelem set)) Set.empty [1..size']
289

    
290
-- | Generates a 'Set' of arbitrary elements.
291
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
292
genSet = genSetHelper [minBound..maxBound]
293

    
294
-- | Generates a 'Set' of arbitrary elements wrapped in a 'ListSet'
295
genListSet :: (Ord a, Bounded a, Enum a) => Maybe Int
296
              -> Gen (BasicTypes.ListSet a)
297
genListSet is = BasicTypes.ListSet <$> genSet is
298

    
299
-- | Generate an arbitrary element of and AndRestArguments field.
300
genAndRestArguments :: Gen (M.Map String J.JSValue)
301
genAndRestArguments = do
302
  n <- choose (0::Int, 10)
303
  let oneParam _ = do
304
                      name <- choose (15 ::Int, 25)
305
                                >>= flip vectorOf (elements tagChar)
306
                      intvalue <- arbitrary
307
                      value <- oneof [ J.JSString . J.toJSString <$> genName
308
                                     , return $ J.showJSON (intvalue :: Int)
309
                                     ]
310
                      return (name, value)
311
  M.fromList `liftM` mapM oneParam [1..n]
312

    
313
-- | Generate an arbitrary IPv4 address in textual form.
314
genIPv4 :: Gen String
315
genIPv4 = do
316
  a <- choose (1::Int, 255)
317
  b <- choose (0::Int, 255)
318
  c <- choose (0::Int, 255)
319
  d <- choose (0::Int, 255)
320
  return . intercalate "." $ map show [a, b, c, d]
321

    
322
genIPv4Address :: Gen IPv4Address
323
genIPv4Address = mkIPv4Address =<< genIPv4
324

    
325
-- | Generate an arbitrary IPv4 network in textual form.
326
genIPv4AddrRange :: Gen String
327
genIPv4AddrRange = do
328
  ip <- genIPv4
329
  netmask <- choose (8::Int, 30)
330
  return $ ip ++ "/" ++ show netmask
331

    
332
genIPv4Network :: Gen IPv4Network
333
genIPv4Network = mkIPv4Network =<< genIPv4AddrRange
334

    
335
-- | Helper function to compute the number of hosts in a network
336
-- given the netmask. (For IPv4 only.)
337
netmask2NumHosts :: Word8 -> Int
338
netmask2NumHosts n = 2^(32-n)
339

    
340
-- | Generates an arbitrary IPv6 network address in textual form.
341
-- The generated address is not simpflified, e. g. an address like
342
-- "2607:f0d0:1002:0051:0000:0000:0000:0004" does not become
343
-- "2607:f0d0:1002:51::4"
344
genIp6Addr :: Gen String
345
genIp6Addr = do
346
  rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
347
  return $ intercalate ":" (map (`showHex` "") rawIp)
348

    
349
-- | Generates an arbitrary IPv6 network in textual form.
350
genIp6Net :: Gen String
351
genIp6Net = do
352
  netmask <- choose (8::Int, 126)
353
  ip <- genIp6Addr
354
  return $ ip ++ "/" ++ show netmask
355

    
356
-- | Generates a valid, arbitrary tag name with respect to the given
357
-- 'TagKind' for opcodes.
358
genOpCodesTagName :: TagKind -> Gen (Maybe String)
359
genOpCodesTagName TagKindCluster = return Nothing
360
genOpCodesTagName _ = Just <$> genFQDN
361

    
362
-- | Generates a valid, arbitrary tag name with respect to the given
363
-- 'TagKind' for Luxi.
364
genLuxiTagName :: TagKind -> Gen String
365
genLuxiTagName TagKindCluster = return ""
366
genLuxiTagName _ = genFQDN
367

    
368
-- * Helper functions
369

    
370
-- | Checks for serialisation idempotence.
371
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
372
testSerialisation a =
373
  case J.readJSON (J.showJSON a) of
374
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
375
    J.Ok a' -> a ==? a'
376

    
377
-- | Checks if the deserializer doesn't accept forbidden values.
378
-- The first argument is ignored, it just enforces the correct type.
379
testDeserialisationFail :: (Eq a, Show a, J.JSON a)
380
                        => a -> J.JSValue -> Property
381
testDeserialisationFail a val =
382
  case liftM (`asTypeOf` a) $ J.readJSON val of
383
    J.Error _ -> passTest
384
    J.Ok x    -> failTest $ "Parsed invalid value " ++ show val ++
385
                            " to: " ++ show x
386

    
387
-- | Result to PropertyM IO.
388
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
389
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
390
resultProp (BasicTypes.Ok  val) = return val
391

    
392
-- | Return the source directory of Ganeti.
393
getSourceDir :: IO FilePath
394
getSourceDir = catchJust (guard . isDoesNotExistError)
395
            (getEnv "TOP_SRCDIR")
396
            (const (return "."))
397

    
398
-- | Returns the path of a file in the test data directory, given its name.
399
testDataFilename :: String -> String -> IO FilePath
400
testDataFilename datadir name = do
401
        src <- getSourceDir
402
        return $ src ++ datadir ++ name
403

    
404
-- | Returns the content of the specified haskell test data file.
405
readTestData :: String -> IO String
406
readTestData filename = do
407
    name <- testDataFilename "/test/data/" filename
408
    readFile name
409

    
410
-- | Generate arbitrary values in the IO monad. This is a simple
411
-- wrapper over 'sample''.
412
genSample :: Gen a -> IO a
413
genSample gen = do
414
  values <- sample' gen
415
  case values of
416
    [] -> error "sample' returned an empty list of values??"
417
    x:_ -> return x
418

    
419
-- | Function for testing whether a file is parsed correctly.
420
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
421
testParser parser fileName expectedContent = do
422
  fileContent <- readTestData fileName
423
  case parseOnly parser $ pack fileContent of
424
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
425
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
426

    
427
-- | Generate a property test for parsers.
428
genPropParser :: (Show a, Eq a) => Parser a -> String -> a -> Property
429
genPropParser parser s expected =
430
  case parseOnly parser $ pack s of
431
    Left msg -> failTest $ "Parsing failed: " ++ msg
432
    Right obtained -> expected ==? obtained
433

    
434
-- | Generate an arbitrary non negative integer number
435
genNonNegative :: Gen Int
436
genNonNegative =
437
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))
438

    
439
-- | Computes the relative error of two 'Double' numbers.
440
--
441
-- This is the \"relative error\" algorithm in
442
-- http:\/\/randomascii.wordpress.com\/2012\/02\/25\/
443
-- comparing-floating-point-numbers-2012-edition (URL split due to too
444
-- long line).
445
relativeError :: Double -> Double -> Double
446
relativeError d1 d2 =
447
  let delta = abs $ d1 - d2
448
      a1 = abs d1
449
      a2 = abs d2
450
      greatest = max a1 a2
451
  in if delta == 0
452
       then 0
453
       else delta / greatest
454

    
455
-- | Helper to a get a temporary file name.
456
getTempFileName :: String -> IO FilePath
457
getTempFileName filename = do
458
  tempdir <- getTemporaryDirectory
459
  (fpath, handle) <- openTempFile tempdir filename
460
  _ <- hClose handle
461
  removeFile fpath
462
  return fpath