Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (10.2 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
  , genSet
50
  , genIp4AddrStr
51
  , genIp4Addr
52
  , genIp4NetWithNetmask
53
  , genIp4Net
54
  , genIp6Addr
55
  , genIp6Net
56
  , netmask2NumHosts
57
  , testSerialisation
58
  , resultProp
59
  , readTestData
60
  , genSample
61
  ) where
62

    
63
import Control.Applicative
64
import Control.Exception (catchJust)
65
import Control.Monad
66
import Data.List
67
import qualified Data.Set as Set
68
import System.Environment (getEnv)
69
import System.Exit (ExitCode(..))
70
import System.IO.Error (isDoesNotExistError)
71
import System.Process (readProcessWithExitCode)
72
import qualified Test.HUnit as HUnit
73
import Test.QuickCheck
74
import Test.QuickCheck.Monadic
75
import qualified Text.JSON as J
76
import Numeric
77

    
78
import qualified Ganeti.BasicTypes as BasicTypes
79
import Ganeti.Types
80

    
81
-- * Constants
82

    
83
-- | Maximum memory (1TiB, somewhat random value).
84
maxMem :: Int
85
maxMem = 1024 * 1024
86

    
87
-- | Maximum disk (8TiB, somewhat random value).
88
maxDsk :: Int
89
maxDsk = 1024 * 1024 * 8
90

    
91
-- | Max CPUs (1024, somewhat random value).
92
maxCpu :: Int
93
maxCpu = 1024
94

    
95
-- | Max vcpu ratio (random value).
96
maxVcpuRatio :: Double
97
maxVcpuRatio = 1024.0
98

    
99
-- | Max spindle ratio (random value).
100
maxSpindleRatio :: Double
101
maxSpindleRatio = 1024.0
102

    
103
-- | Max nodes, used just to limit arbitrary instances for smaller
104
-- opcode definitions (e.g. list of nodes in OpTestDelay).
105
maxNodes :: Int
106
maxNodes = 32
107

    
108
-- | Max opcodes or jobs in a submit job and submit many jobs.
109
maxOpCodes :: Int
110
maxOpCodes = 16
111

    
112
-- * Helper functions
113

    
114
-- | Checks for equality with proper annotation. The first argument is
115
-- the computed value, the second one the expected value.
116
(==?) :: (Show a, Eq a) => a -> a -> Property
117
(==?) x y = printTestCase
118
            ("Expected equality, but got mismatch\nexpected: " ++
119
             show y ++ "\n but got: " ++ show x) (x == y)
120
infix 3 ==?
121

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

    
131
-- | Show a message and fail the test.
132
failTest :: String -> Property
133
failTest msg = printTestCase msg False
134

    
135
-- | A 'True' property.
136
passTest :: Property
137
passTest = property True
138

    
139
-- | Return the python binary to use. If the PYTHON environment
140
-- variable is defined, use its value, otherwise use just \"python\".
141
pythonCmd :: IO String
142
pythonCmd = catchJust (guard . isDoesNotExistError)
143
            (getEnv "PYTHON") (const (return "python"))
144

    
145
-- | Run Python with an expression, returning the exit code, standard
146
-- output and error.
147
runPython :: String -> String -> IO (ExitCode, String, String)
148
runPython expr stdin = do
149
  py_binary <- pythonCmd
150
  readProcessWithExitCode py_binary ["-c", expr] stdin
151

    
152
-- | Check python exit code, and fail via HUnit assertions if
153
-- non-zero. Otherwise, return the standard output.
154
checkPythonResult :: (ExitCode, String, String) -> IO String
155
checkPythonResult (py_code, py_stdout, py_stderr) = do
156
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
157
       ExitSuccess py_code
158
  return py_stdout
159

    
160
-- * Arbitrary instances
161

    
162
-- | Defines a DNS name.
163
newtype DNSChar = DNSChar { dnsGetChar::Char }
164

    
165
instance Arbitrary DNSChar where
166
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
167

    
168
instance Show DNSChar where
169
  show = show . dnsGetChar
170

    
171
-- | Generates a single name component.
172
genName :: Gen String
173
genName = do
174
  n <- choose (1, 16)
175
  dn <- vector n
176
  return (map dnsGetChar dn)
177

    
178
-- | Generates an entire FQDN.
179
genFQDN :: Gen String
180
genFQDN = do
181
  ncomps <- choose (1, 4)
182
  names <- vectorOf ncomps genName
183
  return $ intercalate "." names
184

    
185
-- | Combinator that generates a 'Maybe' using a sub-combinator.
186
genMaybe :: Gen a -> Gen (Maybe a)
187
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
188

    
189
-- | Defines a tag type.
190
newtype TagChar = TagChar { tagGetChar :: Char }
191

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

    
197
instance Arbitrary TagChar where
198
  arbitrary = liftM TagChar $ elements tagChar
199

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

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

    
219
-- | Generates a fields list. This uses the same character set as a
220
-- DNS name (just for simplicity).
221
genFields :: Gen [String]
222
genFields = do
223
  n <- choose (1, 32)
224
  vectorOf n genName
225

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

    
234
newtype SmallRatio = SmallRatio Double deriving Show
235
instance Arbitrary SmallRatio where
236
  arbitrary = liftM SmallRatio $ choose (0, 1)
237

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

    
251
-- | Generates a set of arbitrary elements.
252
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
253
genSet = genSetHelper [minBound..maxBound]
254

    
255
-- | Generate an arbitrary IPv4 address in textual form (non empty).
256
genIp4Addr :: Gen NonEmptyString
257
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
258

    
259
-- | Generate an arbitrary IPv4 address in textual form.
260
genIp4AddrStr :: Gen String
261
genIp4AddrStr = do
262
  a <- choose (1::Int, 255)
263
  b <- choose (0::Int, 255)
264
  c <- choose (0::Int, 255)
265
  d <- choose (0::Int, 255)
266
  return $ intercalate "." (map show [a, b, c, d])
267

    
268
-- | Generates an arbitrary IPv4 address with a given netmask in textual form.
269
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
270
genIp4NetWithNetmask netmask = do
271
  ip <- genIp4AddrStr
272
  mkNonEmpty $ ip ++ "/" ++ show netmask
273

    
274
-- | Generate an arbitrary IPv4 network in textual form.
275
genIp4Net :: Gen NonEmptyString
276
genIp4Net = do
277
  netmask <- choose (8::Int, 30)
278
  genIp4NetWithNetmask netmask
279

    
280
-- | Helper function to compute the number of hosts in a network
281
-- given the netmask. (For IPv4 only.)
282
netmask2NumHosts :: Int -> Int
283
netmask2NumHosts n = 2^(32-n)
284

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

    
294
-- | Generates an arbitrary IPv6 network in textual form.
295
genIp6Net :: Gen String
296
genIp6Net = do
297
  netmask <- choose (8::Int, 126)
298
  ip <- genIp6Addr
299
  return $ ip ++ "/" ++ show netmask
300

    
301
-- * Helper functions
302

    
303
-- | Checks for serialisation idempotence.
304
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
305
testSerialisation a =
306
  case J.readJSON (J.showJSON a) of
307
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
308
    J.Ok a' -> a ==? a'
309

    
310
-- | Result to PropertyM IO.
311
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
312
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
313
resultProp (BasicTypes.Ok  val) = return val
314

    
315
-- | Return the source directory of Ganeti.
316
getSourceDir :: IO FilePath
317
getSourceDir = catchJust (guard . isDoesNotExistError)
318
            (getEnv "TOP_SRCDIR")
319
            (const (return "."))
320

    
321
-- | Returns the path of a file in the test data directory, given its name.
322
testDataFilename :: String -> String -> IO FilePath
323
testDataFilename datadir name = do
324
        src <- getSourceDir
325
        return $ src ++ datadir ++ name
326

    
327
-- | Returns the content of the specified haskell test data file.
328
readTestData :: String -> IO String
329
readTestData filename = do
330
    name <- testDataFilename "/test/data/" filename
331
    readFile name
332

    
333
-- | Generate arbitrary values in the IO monad. This is a simple
334
-- wrapper over 'sample''.
335
genSample :: Gen a -> IO a
336
genSample gen = do
337
  values <- sample' gen
338
  case values of
339
    [] -> error "sample' returned an empty list of values??"
340
    x:_ -> return x