Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (13.4 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
  , resultProp
64
  , readTestData
65
  , genSample
66
  , testParser
67
  , genPropParser
68
  , genNonNegative
69
  , relativeError
70
  ) where
71

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

    
91
import qualified Ganeti.BasicTypes as BasicTypes
92
import Ganeti.Types
93

    
94
-- * Constants
95

    
96
-- | Maximum memory (1TiB, somewhat random value).
97
maxMem :: Int
98
maxMem = 1024 * 1024
99

    
100
-- | Maximum disk (8TiB, somewhat random value).
101
maxDsk :: Int
102
maxDsk = 1024 * 1024 * 8
103

    
104
-- | Max CPUs (1024, somewhat random value).
105
maxCpu :: Int
106
maxCpu = 1024
107

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

    
112
-- | Max vcpu ratio (random value).
113
maxVcpuRatio :: Double
114
maxVcpuRatio = 1024.0
115

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

    
120
-- | Max nodes, used just to limit arbitrary instances for smaller
121
-- opcode definitions (e.g. list of nodes in OpTestDelay).
122
maxNodes :: Int
123
maxNodes = 32
124

    
125
-- | Max opcodes or jobs in a submit job and submit many jobs.
126
maxOpCodes :: Int
127
maxOpCodes = 16
128

    
129
-- * Helper functions
130

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

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

    
148
-- | Show a message and fail the test.
149
failTest :: String -> Property
150
failTest msg = printTestCase msg False
151

    
152
-- | A 'True' property.
153
passTest :: Property
154
passTest = property True
155

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

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

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

    
177
-- * Arbitrary instances
178

    
179
-- | Defines a DNS name.
180
newtype DNSChar = DNSChar { dnsGetChar::Char }
181

    
182
instance Arbitrary DNSChar where
183
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
184

    
185
instance Show DNSChar where
186
  show = show . dnsGetChar
187

    
188
-- | Generates a single name component.
189
genName :: Gen String
190
genName = do
191
  n <- choose (1, 16)
192
  dn <- vector n
193
  return (map dnsGetChar dn)
194

    
195
-- | Generates an entire FQDN.
196
genFQDN :: Gen String
197
genFQDN = do
198
  ncomps <- choose (1, 4)
199
  names <- vectorOf ncomps genName
200
  return $ intercalate "." names
201

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

    
220
-- | Combinator that generates a 'Maybe' using a sub-combinator.
221
genMaybe :: Gen a -> Gen (Maybe a)
222
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
223

    
224
-- | Defines a tag type.
225
newtype TagChar = TagChar { tagGetChar :: Char }
226

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

    
232
instance Arbitrary TagChar where
233
  arbitrary = liftM TagChar $ elements tagChar
234

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

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

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

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

    
269
newtype SmallRatio = SmallRatio Double deriving Show
270
instance Arbitrary SmallRatio where
271
  arbitrary = liftM SmallRatio $ choose (0, 1)
272

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

    
286
-- | Generates a 'Set' of arbitrary elements.
287
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
288
genSet = genSetHelper [minBound..maxBound]
289

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

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

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

    
318
genIPv4Address :: Gen IPv4Address
319
genIPv4Address = mkIPv4Address =<< genIPv4
320

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

    
328
genIPv4Network :: Gen IPv4Network
329
genIPv4Network = mkIPv4Network =<< genIPv4AddrRange
330

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

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

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

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

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

    
364
-- * Helper functions
365

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

    
373
-- | Result to PropertyM IO.
374
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
375
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
376
resultProp (BasicTypes.Ok  val) = return val
377

    
378
-- | Return the source directory of Ganeti.
379
getSourceDir :: IO FilePath
380
getSourceDir = catchJust (guard . isDoesNotExistError)
381
            (getEnv "TOP_SRCDIR")
382
            (const (return "."))
383

    
384
-- | Returns the path of a file in the test data directory, given its name.
385
testDataFilename :: String -> String -> IO FilePath
386
testDataFilename datadir name = do
387
        src <- getSourceDir
388
        return $ src ++ datadir ++ name
389

    
390
-- | Returns the content of the specified haskell test data file.
391
readTestData :: String -> IO String
392
readTestData filename = do
393
    name <- testDataFilename "/test/data/" filename
394
    readFile name
395

    
396
-- | Generate arbitrary values in the IO monad. This is a simple
397
-- wrapper over 'sample''.
398
genSample :: Gen a -> IO a
399
genSample gen = do
400
  values <- sample' gen
401
  case values of
402
    [] -> error "sample' returned an empty list of values??"
403
    x:_ -> return x
404

    
405
-- | Function for testing whether a file is parsed correctly.
406
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
407
testParser parser fileName expectedContent = do
408
  fileContent <- readTestData fileName
409
  case parseOnly parser $ pack fileContent of
410
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
411
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
412

    
413
-- | Generate a property test for parsers.
414
genPropParser :: (Show a, Eq a) => Parser a -> String -> a -> Property
415
genPropParser parser s expected =
416
  case parseOnly parser $ pack s of
417
    Left msg -> failTest $ "Parsing failed: " ++ msg
418
    Right obtained -> expected ==? obtained
419

    
420
-- | Generate an arbitrary non negative integer number
421
genNonNegative :: Gen Int
422
genNonNegative =
423
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))
424

    
425
-- | Computes the relative error of two 'Double' numbers.
426
--
427
-- This is the \"relative error\" algorithm in
428
-- http:\/\/randomascii.wordpress.com\/2012\/02\/25\/
429
-- comparing-floating-point-numbers-2012-edition (URL split due to too
430
-- long line).
431
relativeError :: Double -> Double -> Double
432
relativeError d1 d2 =
433
  let delta = abs $ d1 - d2
434
      a1 = abs d1
435
      a2 = abs d2
436
      greatest = max a1 a2
437
  in if delta == 0
438
       then 0
439
       else delta / greatest