Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 5cbf7832

History | View | Annotate | Download (12 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
  , genIPv4Address
54
  , genIPv4Network
55
  , genIp6Addr
56
  , genIp6Net
57
  , genOpCodesTagName
58
  , genLuxiTagName
59
  , netmask2NumHosts
60
  , testSerialisation
61
  , resultProp
62
  , readTestData
63
  , genSample
64
  , testParser
65
  , genPropParser
66
  , genNonNegative
67
  ) where
68

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

    
87
import qualified Ganeti.BasicTypes as BasicTypes
88
import Ganeti.Types
89

    
90
-- * Constants
91

    
92
-- | Maximum memory (1TiB, somewhat random value).
93
maxMem :: Int
94
maxMem = 1024 * 1024
95

    
96
-- | Maximum disk (8TiB, somewhat random value).
97
maxDsk :: Int
98
maxDsk = 1024 * 1024 * 8
99

    
100
-- | Max CPUs (1024, somewhat random value).
101
maxCpu :: Int
102
maxCpu = 1024
103

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

    
108
-- | Max vcpu ratio (random value).
109
maxVcpuRatio :: Double
110
maxVcpuRatio = 1024.0
111

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

    
116
-- | Max nodes, used just to limit arbitrary instances for smaller
117
-- opcode definitions (e.g. list of nodes in OpTestDelay).
118
maxNodes :: Int
119
maxNodes = 32
120

    
121
-- | Max opcodes or jobs in a submit job and submit many jobs.
122
maxOpCodes :: Int
123
maxOpCodes = 16
124

    
125
-- * Helper functions
126

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

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

    
144
-- | Show a message and fail the test.
145
failTest :: String -> Property
146
failTest msg = printTestCase msg False
147

    
148
-- | A 'True' property.
149
passTest :: Property
150
passTest = property True
151

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

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

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

    
173
-- * Arbitrary instances
174

    
175
-- | Defines a DNS name.
176
newtype DNSChar = DNSChar { dnsGetChar::Char }
177

    
178
instance Arbitrary DNSChar where
179
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
180

    
181
instance Show DNSChar where
182
  show = show . dnsGetChar
183

    
184
-- | Generates a single name component.
185
genName :: Gen String
186
genName = do
187
  n <- choose (1, 16)
188
  dn <- vector n
189
  return (map dnsGetChar dn)
190

    
191
-- | Generates an entire FQDN.
192
genFQDN :: Gen String
193
genFQDN = do
194
  ncomps <- choose (1, 4)
195
  names <- vectorOf ncomps genName
196
  return $ intercalate "." names
197

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

    
216
-- | Combinator that generates a 'Maybe' using a sub-combinator.
217
genMaybe :: Gen a -> Gen (Maybe a)
218
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
219

    
220
-- | Defines a tag type.
221
newtype TagChar = TagChar { tagGetChar :: Char }
222

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

    
228
instance Arbitrary TagChar where
229
  arbitrary = liftM TagChar $ elements tagChar
230

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

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

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

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

    
265
newtype SmallRatio = SmallRatio Double deriving Show
266
instance Arbitrary SmallRatio where
267
  arbitrary = liftM SmallRatio $ choose (0, 1)
268

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

    
282
-- | Generates a set of arbitrary elements.
283
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
284
genSet = genSetHelper [minBound..maxBound]
285

    
286
-- | Generate an arbitrary IPv4 address in textual form.
287
genIPv4 :: Gen String
288
genIPv4 = do
289
  a <- choose (1::Int, 255)
290
  b <- choose (0::Int, 255)
291
  c <- choose (0::Int, 255)
292
  d <- choose (0::Int, 255)
293
  return . intercalate "." $ map show [a, b, c, d]
294

    
295
genIPv4Address :: Gen IPv4Address
296
genIPv4Address = mkIPv4Address =<< genIPv4
297

    
298
-- | Generate an arbitrary IPv4 network in textual form.
299
genIPv4AddrRange :: Gen String
300
genIPv4AddrRange = do
301
  ip <- genIPv4
302
  netmask <- choose (8::Int, 30)
303
  return $ ip ++ "/" ++ show netmask
304

    
305
genIPv4Network :: Gen IPv4Network
306
genIPv4Network = mkIPv4Network =<< genIPv4AddrRange
307

    
308
-- | Helper function to compute the number of hosts in a network
309
-- given the netmask. (For IPv4 only.)
310
netmask2NumHosts :: Word8 -> Int
311
netmask2NumHosts n = 2^(32-n)
312

    
313
-- | Generates an arbitrary IPv6 network address in textual form.
314
-- The generated address is not simpflified, e. g. an address like
315
-- "2607:f0d0:1002:0051:0000:0000:0000:0004" does not become
316
-- "2607:f0d0:1002:51::4"
317
genIp6Addr :: Gen String
318
genIp6Addr = do
319
  rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
320
  return $ intercalate ":" (map (`showHex` "") rawIp)
321

    
322
-- | Generates an arbitrary IPv6 network in textual form.
323
genIp6Net :: Gen String
324
genIp6Net = do
325
  netmask <- choose (8::Int, 126)
326
  ip <- genIp6Addr
327
  return $ ip ++ "/" ++ show netmask
328

    
329
-- | Generates a valid, arbitrary tag name with respect to the given
330
-- 'TagKind' for opcodes.
331
genOpCodesTagName :: TagKind -> Gen (Maybe String)
332
genOpCodesTagName TagKindCluster = return Nothing
333
genOpCodesTagName _ = Just <$> genFQDN
334

    
335
-- | Generates a valid, arbitrary tag name with respect to the given
336
-- 'TagKind' for Luxi.
337
genLuxiTagName :: TagKind -> Gen String
338
genLuxiTagName TagKindCluster = return ""
339
genLuxiTagName _ = genFQDN
340

    
341
-- * Helper functions
342

    
343
-- | Checks for serialisation idempotence.
344
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
345
testSerialisation a =
346
  case J.readJSON (J.showJSON a) of
347
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
348
    J.Ok a' -> a ==? a'
349

    
350
-- | Result to PropertyM IO.
351
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
352
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
353
resultProp (BasicTypes.Ok  val) = return val
354

    
355
-- | Return the source directory of Ganeti.
356
getSourceDir :: IO FilePath
357
getSourceDir = catchJust (guard . isDoesNotExistError)
358
            (getEnv "TOP_SRCDIR")
359
            (const (return "."))
360

    
361
-- | Returns the path of a file in the test data directory, given its name.
362
testDataFilename :: String -> String -> IO FilePath
363
testDataFilename datadir name = do
364
        src <- getSourceDir
365
        return $ src ++ datadir ++ name
366

    
367
-- | Returns the content of the specified haskell test data file.
368
readTestData :: String -> IO String
369
readTestData filename = do
370
    name <- testDataFilename "/test/data/" filename
371
    readFile name
372

    
373
-- | Generate arbitrary values in the IO monad. This is a simple
374
-- wrapper over 'sample''.
375
genSample :: Gen a -> IO a
376
genSample gen = do
377
  values <- sample' gen
378
  case values of
379
    [] -> error "sample' returned an empty list of values??"
380
    x:_ -> return x
381

    
382
-- | Function for testing whether a file is parsed correctly.
383
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
384
testParser parser fileName expectedContent = do
385
  fileContent <- readTestData fileName
386
  case parseOnly parser $ pack fileContent of
387
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
388
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
389

    
390
-- | Generate a property test for parsers.
391
genPropParser :: (Show a, Eq a) => Parser a -> String -> a -> Property
392
genPropParser parser s expected =
393
  case parseOnly parser $ pack s of
394
    Left msg -> failTest $ "Parsing failed: " ++ msg
395
    Right obtained -> expected ==? obtained
396

    
397
-- | Generate an arbitrary non negative integer number
398
genNonNegative :: Gen Int
399
genNonNegative =
400
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))