Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 91f0dc1e

History | View | Annotate | Download (14.6 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
  , testArraySerialisation
64
  , testDeserialisationFail
65
  , resultProp
66
  , readTestData
67
  , genSample
68
  , testParser
69
  , genPropParser
70
  , genNonNegative
71
  , relativeError
72
  , getTempFileName
73
  ) where
74

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

    
96
import qualified Ganeti.BasicTypes as BasicTypes
97
import Ganeti.JSON (ArrayObject(..))
98
import Ganeti.Types
99

    
100
-- * Constants
101

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

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

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

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

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

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

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

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

    
135
-- * Helper functions
136

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

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

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

    
158
-- | A 'True' property.
159
passTest :: Property
160
passTest = property True
161

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

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

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

    
183
-- * Arbitrary instances
184

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

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

    
191
instance Show DNSChar where
192
  show = show . dnsGetChar
193

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

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

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

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

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

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

    
238
instance Arbitrary TagChar where
239
  arbitrary = liftM TagChar $ elements tagChar
240

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

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

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

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

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

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

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

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

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

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

    
324
genIPv4Address :: Gen IPv4Address
325
genIPv4Address = mkIPv4Address =<< genIPv4
326

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

    
334
genIPv4Network :: Gen IPv4Network
335
genIPv4Network = mkIPv4Network =<< genIPv4AddrRange
336

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

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

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

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

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

    
370
-- * Helper functions
371

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

    
379
-- | Checks for array serialisation idempotence.
380
testArraySerialisation :: (Eq a, Show a, ArrayObject a) => a -> Property
381
testArraySerialisation a =
382
  case fromJSArray (toJSArray a) of
383
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
384
    J.Ok a' -> a ==? a'
385

    
386
-- | Checks if the deserializer doesn't accept forbidden values.
387
-- The first argument is ignored, it just enforces the correct type.
388
testDeserialisationFail :: (Eq a, Show a, J.JSON a)
389
                        => a -> J.JSValue -> Property
390
testDeserialisationFail a val =
391
  case liftM (`asTypeOf` a) $ J.readJSON val of
392
    J.Error _ -> passTest
393
    J.Ok x    -> failTest $ "Parsed invalid value " ++ show val ++
394
                            " to: " ++ show x
395

    
396
-- | Result to PropertyM IO.
397
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
398
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
399
resultProp (BasicTypes.Ok  val) = return val
400

    
401
-- | Return the source directory of Ganeti.
402
getSourceDir :: IO FilePath
403
getSourceDir = catchJust (guard . isDoesNotExistError)
404
            (getEnv "TOP_SRCDIR")
405
            (const (return "."))
406

    
407
-- | Returns the path of a file in the test data directory, given its name.
408
testDataFilename :: String -> String -> IO FilePath
409
testDataFilename datadir name = do
410
        src <- getSourceDir
411
        return $ src ++ datadir ++ name
412

    
413
-- | Returns the content of the specified haskell test data file.
414
readTestData :: String -> IO String
415
readTestData filename = do
416
    name <- testDataFilename "/test/data/" filename
417
    readFile name
418

    
419
-- | Generate arbitrary values in the IO monad. This is a simple
420
-- wrapper over 'sample''.
421
genSample :: Gen a -> IO a
422
genSample gen = do
423
  values <- sample' gen
424
  case values of
425
    [] -> error "sample' returned an empty list of values??"
426
    x:_ -> return x
427

    
428
-- | Function for testing whether a file is parsed correctly.
429
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
430
testParser parser fileName expectedContent = do
431
  fileContent <- readTestData fileName
432
  case parseOnly parser $ pack fileContent of
433
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
434
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
435

    
436
-- | Generate a property test for parsers.
437
genPropParser :: (Show a, Eq a) => Parser a -> String -> a -> Property
438
genPropParser parser s expected =
439
  case parseOnly parser $ pack s of
440
    Left msg -> failTest $ "Parsing failed: " ++ msg
441
    Right obtained -> expected ==? obtained
442

    
443
-- | Generate an arbitrary non negative integer number
444
genNonNegative :: Gen Int
445
genNonNegative =
446
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))
447

    
448
-- | Computes the relative error of two 'Double' numbers.
449
--
450
-- This is the \"relative error\" algorithm in
451
-- http:\/\/randomascii.wordpress.com\/2012\/02\/25\/
452
-- comparing-floating-point-numbers-2012-edition (URL split due to too
453
-- long line).
454
relativeError :: Double -> Double -> Double
455
relativeError d1 d2 =
456
  let delta = abs $ d1 - d2
457
      a1 = abs d1
458
      a2 = abs d2
459
      greatest = max a1 a2
460
  in if delta == 0
461
       then 0
462
       else delta / greatest
463

    
464
-- | Helper to a get a temporary file name.
465
getTempFileName :: String -> IO FilePath
466
getTempFileName filename = do
467
  tempdir <- getTemporaryDirectory
468
  (fpath, handle) <- openTempFile tempdir filename
469
  _ <- hClose handle
470
  removeFile fpath
471
  return fpath