Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 3a991f2d

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
  , 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
  ) where
63

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

    
80
import qualified Ganeti.BasicTypes as BasicTypes
81
import Ganeti.Types
82

    
83
-- * Constants
84

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

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

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

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

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

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

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

    
114
-- * Helper functions
115

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

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

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

    
137
-- | A 'True' property.
138
passTest :: Property
139
passTest = property True
140

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

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

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

    
162
-- * Arbitrary instances
163

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

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

    
170
instance Show DNSChar where
171
  show = show . dnsGetChar
172

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

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

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

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

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

    
199
instance Arbitrary TagChar where
200
  arbitrary = liftM TagChar $ elements tagChar
201

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
303
-- * Helper functions
304

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

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

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

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

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

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