Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 688f35e6

History | View | Annotate | Download (11.5 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
  , genIp4AddrStr
54
  , genIp4Addr
55
  , genIp4NetWithNetmask
56
  , genIp4Net
57
  , genIp6Addr
58
  , genIp6Net
59
  , netmask2NumHosts
60
  , testSerialisation
61
  , resultProp
62
  , readTestData
63
  , genSample
64
  , testParser
65
  , genNonNegative
66
  ) where
67

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

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

    
89
-- * Constants
90

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

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

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

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

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

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

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

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

    
124
-- * Helper functions
125

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

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

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

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

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

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

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

    
172
-- * Arbitrary instances
173

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
285
-- | Generate an arbitrary IPv4 address in textual form (non empty).
286
genIp4Addr :: Gen NonEmptyString
287
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
288

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

    
298
-- | Generates an arbitrary IPv4 address with a given netmask in textual form.
299
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
300
genIp4NetWithNetmask netmask = do
301
  ip <- genIp4AddrStr
302
  mkNonEmpty $ ip ++ "/" ++ show netmask
303

    
304
-- | Generate an arbitrary IPv4 network in textual form.
305
genIp4Net :: Gen NonEmptyString
306
genIp4Net = do
307
  netmask <- choose (8::Int, 30)
308
  genIp4NetWithNetmask netmask
309

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

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

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

    
331
-- * Helper functions
332

    
333
-- | Checks for serialisation idempotence.
334
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
335
testSerialisation a =
336
  case J.readJSON (J.showJSON a) of
337
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
338
    J.Ok a' -> a ==? a'
339

    
340
-- | Result to PropertyM IO.
341
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
342
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
343
resultProp (BasicTypes.Ok  val) = return val
344

    
345
-- | Return the source directory of Ganeti.
346
getSourceDir :: IO FilePath
347
getSourceDir = catchJust (guard . isDoesNotExistError)
348
            (getEnv "TOP_SRCDIR")
349
            (const (return "."))
350

    
351
-- | Returns the path of a file in the test data directory, given its name.
352
testDataFilename :: String -> String -> IO FilePath
353
testDataFilename datadir name = do
354
        src <- getSourceDir
355
        return $ src ++ datadir ++ name
356

    
357
-- | Returns the content of the specified haskell test data file.
358
readTestData :: String -> IO String
359
readTestData filename = do
360
    name <- testDataFilename "/test/data/" filename
361
    readFile name
362

    
363
-- | Generate arbitrary values in the IO monad. This is a simple
364
-- wrapper over 'sample''.
365
genSample :: Gen a -> IO a
366
genSample gen = do
367
  values <- sample' gen
368
  case values of
369
    [] -> error "sample' returned an empty list of values??"
370
    x:_ -> return x
371

    
372
-- | Function for testing whether a file is parsed correctly.
373
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
374
testParser parser fileName expectedContent = do
375
  fileContent <- readTestData fileName
376
  case parseOnly parser $ pack fileContent of
377
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
378
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
379

    
380
-- | Generate an arbitrary non negative integer number
381
genNonNegative :: Gen Int
382
genNonNegative =
383
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))