Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11 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
  , genMaybe
46
  , genTags
47
  , genFields
48
  , genUniquesList
49
  , SmallRatio(..)
50
  , genSetHelper
51
  , genSet
52
  , genIp4AddrStr
53
  , genIp4Addr
54
  , genIp4NetWithNetmask
55
  , genIp4Net
56
  , genIp6Addr
57
  , genIp6Net
58
  , netmask2NumHosts
59
  , testSerialisation
60
  , resultProp
61
  , readTestData
62
  , genSample
63
  , testParser
64
  , genNonNegative
65
  ) where
66

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

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

    
88
-- * Constants
89

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

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

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

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

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

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

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

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

    
123
-- * Helper functions
124

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

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

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

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

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

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

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

    
171
-- * Arbitrary instances
172

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

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

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

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

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

    
196
-- | Combinator that generates a 'Maybe' using a sub-combinator.
197
genMaybe :: Gen a -> Gen (Maybe a)
198
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
199

    
200
-- | Defines a tag type.
201
newtype TagChar = TagChar { tagGetChar :: Char }
202

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

    
208
instance Arbitrary TagChar where
209
  arbitrary = liftM TagChar $ elements tagChar
210

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

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

    
230
-- | Generates a fields list. This uses the same character set as a
231
-- DNS name (just for simplicity).
232
genFields :: Gen [String]
233
genFields = do
234
  n <- choose (1, 32)
235
  vectorOf n genName
236

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

    
245
newtype SmallRatio = SmallRatio Double deriving Show
246
instance Arbitrary SmallRatio where
247
  arbitrary = liftM SmallRatio $ choose (0, 1)
248

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

    
262
-- | Generates a set of arbitrary elements.
263
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
264
genSet = genSetHelper [minBound..maxBound]
265

    
266
-- | Generate an arbitrary IPv4 address in textual form (non empty).
267
genIp4Addr :: Gen NonEmptyString
268
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
269

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

    
279
-- | Generates an arbitrary IPv4 address with a given netmask in textual form.
280
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
281
genIp4NetWithNetmask netmask = do
282
  ip <- genIp4AddrStr
283
  mkNonEmpty $ ip ++ "/" ++ show netmask
284

    
285
-- | Generate an arbitrary IPv4 network in textual form.
286
genIp4Net :: Gen NonEmptyString
287
genIp4Net = do
288
  netmask <- choose (8::Int, 30)
289
  genIp4NetWithNetmask netmask
290

    
291
-- | Helper function to compute the number of hosts in a network
292
-- given the netmask. (For IPv4 only.)
293
netmask2NumHosts :: Word8 -> Int
294
netmask2NumHosts n = 2^(32-n)
295

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

    
305
-- | Generates an arbitrary IPv6 network in textual form.
306
genIp6Net :: Gen String
307
genIp6Net = do
308
  netmask <- choose (8::Int, 126)
309
  ip <- genIp6Addr
310
  return $ ip ++ "/" ++ show netmask
311

    
312
-- * Helper functions
313

    
314
-- | Checks for serialisation idempotence.
315
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
316
testSerialisation a =
317
  case J.readJSON (J.showJSON a) of
318
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
319
    J.Ok a' -> a ==? a'
320

    
321
-- | Result to PropertyM IO.
322
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
323
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
324
resultProp (BasicTypes.Ok  val) = return val
325

    
326
-- | Return the source directory of Ganeti.
327
getSourceDir :: IO FilePath
328
getSourceDir = catchJust (guard . isDoesNotExistError)
329
            (getEnv "TOP_SRCDIR")
330
            (const (return "."))
331

    
332
-- | Returns the path of a file in the test data directory, given its name.
333
testDataFilename :: String -> String -> IO FilePath
334
testDataFilename datadir name = do
335
        src <- getSourceDir
336
        return $ src ++ datadir ++ name
337

    
338
-- | Returns the content of the specified haskell test data file.
339
readTestData :: String -> IO String
340
readTestData filename = do
341
    name <- testDataFilename "/test/data/" filename
342
    readFile name
343

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

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

    
361
-- | Generate an arbitrary non negative integer number
362
genNonNegative :: Gen Int
363
genNonNegative =
364
  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))