Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (10.9 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
  , maxVcpuRatio
31
  , maxSpindleRatio
32
  , maxNodes
33
  , maxOpCodes
34
  , (==?)
35
  , (/=?)
36
  , failTest
37
  , passTest
38
  , pythonCmd
39
  , runPython
40
  , checkPythonResult
41
  , DNSChar(..)
42
  , genName
43
  , genFQDN
44
  , genMaybe
45
  , genTags
46
  , genFields
47
  , genUniquesList
48
  , SmallRatio(..)
49
  , genSetHelper
50
  , genSet
51
  , genIp4AddrStr
52
  , genIp4Addr
53
  , genIp4NetWithNetmask
54
  , genIp4Net
55
  , genIp6Addr
56
  , genIp6Net
57
  , netmask2NumHosts
58
  , testSerialisation
59
  , resultProp
60
  , readTestData
61
  , genSample
62
  , testParser
63
  , genNonNegative
64
  ) where
65

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

    
84
import qualified Ganeti.BasicTypes as BasicTypes
85
import Ganeti.Types
86

    
87
-- * Constants
88

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

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

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

    
101
-- | Max vcpu ratio (random value).
102
maxVcpuRatio :: Double
103
maxVcpuRatio = 1024.0
104

    
105
-- | Max spindle ratio (random value).
106
maxSpindleRatio :: Double
107
maxSpindleRatio = 1024.0
108

    
109
-- | Max nodes, used just to limit arbitrary instances for smaller
110
-- opcode definitions (e.g. list of nodes in OpTestDelay).
111
maxNodes :: Int
112
maxNodes = 32
113

    
114
-- | Max opcodes or jobs in a submit job and submit many jobs.
115
maxOpCodes :: Int
116
maxOpCodes = 16
117

    
118
-- * Helper functions
119

    
120
-- | Checks for equality with proper annotation. The first argument is
121
-- the computed value, the second one the expected value.
122
(==?) :: (Show a, Eq a) => a -> a -> Property
123
(==?) x y = printTestCase
124
            ("Expected equality, but got mismatch\nexpected: " ++
125
             show y ++ "\n but got: " ++ show x) (x == y)
126
infix 3 ==?
127

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

    
137
-- | Show a message and fail the test.
138
failTest :: String -> Property
139
failTest msg = printTestCase msg False
140

    
141
-- | A 'True' property.
142
passTest :: Property
143
passTest = property True
144

    
145
-- | Return the python binary to use. If the PYTHON environment
146
-- variable is defined, use its value, otherwise use just \"python\".
147
pythonCmd :: IO String
148
pythonCmd = catchJust (guard . isDoesNotExistError)
149
            (getEnv "PYTHON") (const (return "python"))
150

    
151
-- | Run Python with an expression, returning the exit code, standard
152
-- output and error.
153
runPython :: String -> String -> IO (ExitCode, String, String)
154
runPython expr stdin = do
155
  py_binary <- pythonCmd
156
  readProcessWithExitCode py_binary ["-c", expr] stdin
157

    
158
-- | Check python exit code, and fail via HUnit assertions if
159
-- non-zero. Otherwise, return the standard output.
160
checkPythonResult :: (ExitCode, String, String) -> IO String
161
checkPythonResult (py_code, py_stdout, py_stderr) = do
162
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
163
       ExitSuccess py_code
164
  return py_stdout
165

    
166
-- * Arbitrary instances
167

    
168
-- | Defines a DNS name.
169
newtype DNSChar = DNSChar { dnsGetChar::Char }
170

    
171
instance Arbitrary DNSChar where
172
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
173

    
174
instance Show DNSChar where
175
  show = show . dnsGetChar
176

    
177
-- | Generates a single name component.
178
genName :: Gen String
179
genName = do
180
  n <- choose (1, 16)
181
  dn <- vector n
182
  return (map dnsGetChar dn)
183

    
184
-- | Generates an entire FQDN.
185
genFQDN :: Gen String
186
genFQDN = do
187
  ncomps <- choose (1, 4)
188
  names <- vectorOf ncomps genName
189
  return $ intercalate "." names
190

    
191
-- | Combinator that generates a 'Maybe' using a sub-combinator.
192
genMaybe :: Gen a -> Gen (Maybe a)
193
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
194

    
195
-- | Defines a tag type.
196
newtype TagChar = TagChar { tagGetChar :: Char }
197

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

    
203
instance Arbitrary TagChar where
204
  arbitrary = liftM TagChar $ elements tagChar
205

    
206
-- | Generates a tag
207
genTag :: Gen [TagChar]
208
genTag = do
209
  -- the correct value would be C.maxTagLen, but that's way too
210
  -- verbose in unittests, and at the moment I don't see any possible
211
  -- bugs with longer tags and the way we use tags in htools
212
  n <- choose (1, 10)
213
  vector n
214

    
215
-- | Generates a list of tags (correctly upper bounded).
216
genTags :: Gen [String]
217
genTags = do
218
  -- the correct value would be C.maxTagsPerObj, but per the comment
219
  -- in genTag, we don't use tags enough in htools to warrant testing
220
  -- such big values
221
  n <- choose (0, 10::Int)
222
  tags <- mapM (const genTag) [1..n]
223
  return $ map (map tagGetChar) tags
224

    
225
-- | Generates a fields list. This uses the same character set as a
226
-- DNS name (just for simplicity).
227
genFields :: Gen [String]
228
genFields = do
229
  n <- choose (1, 32)
230
  vectorOf n genName
231

    
232
-- | Generates a list of a given size with non-duplicate elements.
233
genUniquesList :: (Eq a, Arbitrary a, Ord a) => Int -> Gen a -> Gen [a]
234
genUniquesList cnt generator = do
235
  set <- foldM (\set _ -> do
236
                  newelem <- generator `suchThat` (`Set.notMember` set)
237
                  return (Set.insert newelem set)) Set.empty [1..cnt]
238
  return $ Set.toList set
239

    
240
newtype SmallRatio = SmallRatio Double deriving Show
241
instance Arbitrary SmallRatio where
242
  arbitrary = liftM SmallRatio $ choose (0, 1)
243

    
244
-- | Helper for 'genSet', declared separately due to type constraints.
245
genSetHelper :: (Ord a) => [a] -> Maybe Int -> Gen (Set.Set a)
246
genSetHelper candidates size = do
247
  size' <- case size of
248
             Nothing -> choose (0, length candidates)
249
             Just s | s > length candidates ->
250
                        error $ "Invalid size " ++ show s ++ ", maximum is " ++
251
                                show (length candidates)
252
                    | otherwise -> return s
253
  foldM (\set _ -> do
254
           newelem <- elements candidates `suchThat` (`Set.notMember` set)
255
           return (Set.insert newelem set)) Set.empty [1..size']
256

    
257
-- | Generates a set of arbitrary elements.
258
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
259
genSet = genSetHelper [minBound..maxBound]
260

    
261
-- | Generate an arbitrary IPv4 address in textual form (non empty).
262
genIp4Addr :: Gen NonEmptyString
263
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
264

    
265
-- | Generate an arbitrary IPv4 address in textual form.
266
genIp4AddrStr :: Gen String
267
genIp4AddrStr = do
268
  a <- choose (1::Int, 255)
269
  b <- choose (0::Int, 255)
270
  c <- choose (0::Int, 255)
271
  d <- choose (0::Int, 255)
272
  return $ intercalate "." (map show [a, b, c, d])
273

    
274
-- | Generates an arbitrary IPv4 address with a given netmask in textual form.
275
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
276
genIp4NetWithNetmask netmask = do
277
  ip <- genIp4AddrStr
278
  mkNonEmpty $ ip ++ "/" ++ show netmask
279

    
280
-- | Generate an arbitrary IPv4 network in textual form.
281
genIp4Net :: Gen NonEmptyString
282
genIp4Net = do
283
  netmask <- choose (8::Int, 30)
284
  genIp4NetWithNetmask netmask
285

    
286
-- | Helper function to compute the number of hosts in a network
287
-- given the netmask. (For IPv4 only.)
288
netmask2NumHosts :: Word8 -> Int
289
netmask2NumHosts n = 2^(32-n)
290

    
291
-- | Generates an arbitrary IPv6 network address in textual form.
292
-- The generated address is not simpflified, e. g. an address like
293
-- "2607:f0d0:1002:0051:0000:0000:0000:0004" does not become
294
-- "2607:f0d0:1002:51::4"
295
genIp6Addr :: Gen String
296
genIp6Addr = do
297
  rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
298
  return $ intercalate ":" (map (`showHex` "") rawIp)
299

    
300
-- | Generates an arbitrary IPv6 network in textual form.
301
genIp6Net :: Gen String
302
genIp6Net = do
303
  netmask <- choose (8::Int, 126)
304
  ip <- genIp6Addr
305
  return $ ip ++ "/" ++ show netmask
306

    
307
-- * Helper functions
308

    
309
-- | Checks for serialisation idempotence.
310
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
311
testSerialisation a =
312
  case J.readJSON (J.showJSON a) of
313
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
314
    J.Ok a' -> a ==? a'
315

    
316
-- | Result to PropertyM IO.
317
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
318
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
319
resultProp (BasicTypes.Ok  val) = return val
320

    
321
-- | Return the source directory of Ganeti.
322
getSourceDir :: IO FilePath
323
getSourceDir = catchJust (guard . isDoesNotExistError)
324
            (getEnv "TOP_SRCDIR")
325
            (const (return "."))
326

    
327
-- | Returns the path of a file in the test data directory, given its name.
328
testDataFilename :: String -> String -> IO FilePath
329
testDataFilename datadir name = do
330
        src <- getSourceDir
331
        return $ src ++ datadir ++ name
332

    
333
-- | Returns the content of the specified haskell test data file.
334
readTestData :: String -> IO String
335
readTestData filename = do
336
    name <- testDataFilename "/test/data/" filename
337
    readFile name
338

    
339
-- | Generate arbitrary values in the IO monad. This is a simple
340
-- wrapper over 'sample''.
341
genSample :: Gen a -> IO a
342
genSample gen = do
343
  values <- sample' gen
344
  case values of
345
    [] -> error "sample' returned an empty list of values??"
346
    x:_ -> return x
347

    
348
-- | Function for testing whether a file is parsed correctly.
349
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
350
testParser parser fileName expectedContent = do
351
  fileContent <- readTestData fileName
352
  case parseOnly parser $ pack fileContent of
353
    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
354
    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
355

    
356
-- | Generate an arbitrary non negative integer number
357
genNonNegative :: Gen Int
358
genNonNegative =
359
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))