Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 06c2fb4a

History | View | Annotate | Download (10.2 kB)

1 2733df51 Iustin Pop
{-| Unittest helpers for ganeti-htools.
2 2733df51 Iustin Pop
3 2733df51 Iustin Pop
-}
4 2733df51 Iustin Pop
5 2733df51 Iustin Pop
{-
6 2733df51 Iustin Pop
7 72747d91 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
8 2733df51 Iustin Pop
9 2733df51 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 2733df51 Iustin Pop
it under the terms of the GNU General Public License as published by
11 2733df51 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 2733df51 Iustin Pop
(at your option) any later version.
13 2733df51 Iustin Pop
14 2733df51 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 2733df51 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 2733df51 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 2733df51 Iustin Pop
General Public License for more details.
18 2733df51 Iustin Pop
19 2733df51 Iustin Pop
You should have received a copy of the GNU General Public License
20 2733df51 Iustin Pop
along with this program; if not, write to the Free Software
21 2733df51 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 2733df51 Iustin Pop
02110-1301, USA.
23 2733df51 Iustin Pop
24 2733df51 Iustin Pop
-}
25 2733df51 Iustin Pop
26 dde85e1e Iustin Pop
module Test.Ganeti.TestCommon
27 dde85e1e Iustin Pop
  ( maxMem
28 dde85e1e Iustin Pop
  , maxDsk
29 dde85e1e Iustin Pop
  , maxCpu
30 dde85e1e Iustin Pop
  , maxVcpuRatio
31 dde85e1e Iustin Pop
  , maxSpindleRatio
32 dde85e1e Iustin Pop
  , maxNodes
33 dde85e1e Iustin Pop
  , maxOpCodes
34 dde85e1e Iustin Pop
  , (==?)
35 dde85e1e Iustin Pop
  , (/=?)
36 dde85e1e Iustin Pop
  , failTest
37 dde85e1e Iustin Pop
  , passTest
38 dde85e1e Iustin Pop
  , pythonCmd
39 dde85e1e Iustin Pop
  , runPython
40 dde85e1e Iustin Pop
  , checkPythonResult
41 dde85e1e Iustin Pop
  , DNSChar(..)
42 dde85e1e Iustin Pop
  , genName
43 dde85e1e Iustin Pop
  , genFQDN
44 dde85e1e Iustin Pop
  , genMaybe
45 dde85e1e Iustin Pop
  , genTags
46 dde85e1e Iustin Pop
  , genFields
47 dde85e1e Iustin Pop
  , genUniquesList
48 dde85e1e Iustin Pop
  , SmallRatio(..)
49 491d02ca Iustin Pop
  , genSetHelper
50 dde85e1e Iustin Pop
  , genSet
51 dde85e1e Iustin Pop
  , genIp4AddrStr
52 dde85e1e Iustin Pop
  , genIp4Addr
53 dde85e1e Iustin Pop
  , genIp4NetWithNetmask
54 dde85e1e Iustin Pop
  , genIp4Net
55 dde85e1e Iustin Pop
  , genIp6Addr
56 dde85e1e Iustin Pop
  , genIp6Net
57 dde85e1e Iustin Pop
  , netmask2NumHosts
58 dde85e1e Iustin Pop
  , testSerialisation
59 dde85e1e Iustin Pop
  , resultProp
60 dde85e1e Iustin Pop
  , readTestData
61 dde85e1e Iustin Pop
  , genSample
62 dde85e1e Iustin Pop
  ) where
63 2733df51 Iustin Pop
64 2733df51 Iustin Pop
import Control.Applicative
65 aed2325f Iustin Pop
import Control.Exception (catchJust)
66 aed2325f Iustin Pop
import Control.Monad
67 2733df51 Iustin Pop
import Data.List
68 3a991f2d Iustin Pop
import Data.Word
69 2a8efa13 Iustin Pop
import qualified Data.Set as Set
70 aed2325f Iustin Pop
import System.Environment (getEnv)
71 aed2325f Iustin Pop
import System.Exit (ExitCode(..))
72 aed2325f Iustin Pop
import System.IO.Error (isDoesNotExistError)
73 aed2325f Iustin Pop
import System.Process (readProcessWithExitCode)
74 2a8efa13 Iustin Pop
import qualified Test.HUnit as HUnit
75 2a8efa13 Iustin Pop
import Test.QuickCheck
76 2a8efa13 Iustin Pop
import Test.QuickCheck.Monadic
77 2a8efa13 Iustin Pop
import qualified Text.JSON as J
78 0b288282 Helga Velroyen
import Numeric
79 2733df51 Iustin Pop
80 b9bdc10e Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
81 0b288282 Helga Velroyen
import Ganeti.Types
82 b9bdc10e Iustin Pop
83 2733df51 Iustin Pop
-- * Constants
84 2733df51 Iustin Pop
85 2733df51 Iustin Pop
-- | Maximum memory (1TiB, somewhat random value).
86 2733df51 Iustin Pop
maxMem :: Int
87 2733df51 Iustin Pop
maxMem = 1024 * 1024
88 2733df51 Iustin Pop
89 2733df51 Iustin Pop
-- | Maximum disk (8TiB, somewhat random value).
90 2733df51 Iustin Pop
maxDsk :: Int
91 2733df51 Iustin Pop
maxDsk = 1024 * 1024 * 8
92 2733df51 Iustin Pop
93 2733df51 Iustin Pop
-- | Max CPUs (1024, somewhat random value).
94 2733df51 Iustin Pop
maxCpu :: Int
95 2733df51 Iustin Pop
maxCpu = 1024
96 2733df51 Iustin Pop
97 2733df51 Iustin Pop
-- | Max vcpu ratio (random value).
98 2733df51 Iustin Pop
maxVcpuRatio :: Double
99 2733df51 Iustin Pop
maxVcpuRatio = 1024.0
100 2733df51 Iustin Pop
101 2733df51 Iustin Pop
-- | Max spindle ratio (random value).
102 2733df51 Iustin Pop
maxSpindleRatio :: Double
103 2733df51 Iustin Pop
maxSpindleRatio = 1024.0
104 2733df51 Iustin Pop
105 2733df51 Iustin Pop
-- | Max nodes, used just to limit arbitrary instances for smaller
106 2733df51 Iustin Pop
-- opcode definitions (e.g. list of nodes in OpTestDelay).
107 2733df51 Iustin Pop
maxNodes :: Int
108 2733df51 Iustin Pop
maxNodes = 32
109 2733df51 Iustin Pop
110 2733df51 Iustin Pop
-- | Max opcodes or jobs in a submit job and submit many jobs.
111 2733df51 Iustin Pop
maxOpCodes :: Int
112 2733df51 Iustin Pop
maxOpCodes = 16
113 2733df51 Iustin Pop
114 2733df51 Iustin Pop
-- * Helper functions
115 2733df51 Iustin Pop
116 41eb900e Iustin Pop
-- | Checks for equality with proper annotation. The first argument is
117 41eb900e Iustin Pop
-- the computed value, the second one the expected value.
118 2733df51 Iustin Pop
(==?) :: (Show a, Eq a) => a -> a -> Property
119 2733df51 Iustin Pop
(==?) x y = printTestCase
120 41eb900e Iustin Pop
            ("Expected equality, but got mismatch\nexpected: " ++
121 a309a3b4 Iustin Pop
             show y ++ "\n but got: " ++ show x) (x == y)
122 2733df51 Iustin Pop
infix 3 ==?
123 2733df51 Iustin Pop
124 41eb900e Iustin Pop
-- | Checks for inequality with proper annotation. The first argument
125 41eb900e Iustin Pop
-- is the computed value, the second one the expected (not equal)
126 41eb900e Iustin Pop
-- value.
127 dddb2bc9 Helga Velroyen
(/=?) :: (Show a, Eq a) => a -> a -> Property
128 dddb2bc9 Helga Velroyen
(/=?) x y = printTestCase
129 dddb2bc9 Helga Velroyen
            ("Expected inequality, but got equality: '" ++
130 dddb2bc9 Helga Velroyen
             show x ++ "'.") (x /= y)
131 dddb2bc9 Helga Velroyen
infix 3 /=?
132 dddb2bc9 Helga Velroyen
133 2733df51 Iustin Pop
-- | Show a message and fail the test.
134 2733df51 Iustin Pop
failTest :: String -> Property
135 2733df51 Iustin Pop
failTest msg = printTestCase msg False
136 2733df51 Iustin Pop
137 2e0bb81d Iustin Pop
-- | A 'True' property.
138 2e0bb81d Iustin Pop
passTest :: Property
139 2e0bb81d Iustin Pop
passTest = property True
140 2e0bb81d Iustin Pop
141 aed2325f Iustin Pop
-- | Return the python binary to use. If the PYTHON environment
142 aed2325f Iustin Pop
-- variable is defined, use its value, otherwise use just \"python\".
143 aed2325f Iustin Pop
pythonCmd :: IO String
144 aed2325f Iustin Pop
pythonCmd = catchJust (guard . isDoesNotExistError)
145 aed2325f Iustin Pop
            (getEnv "PYTHON") (const (return "python"))
146 aed2325f Iustin Pop
147 aed2325f Iustin Pop
-- | Run Python with an expression, returning the exit code, standard
148 aed2325f Iustin Pop
-- output and error.
149 aed2325f Iustin Pop
runPython :: String -> String -> IO (ExitCode, String, String)
150 aed2325f Iustin Pop
runPython expr stdin = do
151 aed2325f Iustin Pop
  py_binary <- pythonCmd
152 aed2325f Iustin Pop
  readProcessWithExitCode py_binary ["-c", expr] stdin
153 aed2325f Iustin Pop
154 aed2325f Iustin Pop
-- | Check python exit code, and fail via HUnit assertions if
155 aed2325f Iustin Pop
-- non-zero. Otherwise, return the standard output.
156 aed2325f Iustin Pop
checkPythonResult :: (ExitCode, String, String) -> IO String
157 aed2325f Iustin Pop
checkPythonResult (py_code, py_stdout, py_stderr) = do
158 aed2325f Iustin Pop
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
159 aed2325f Iustin Pop
       ExitSuccess py_code
160 aed2325f Iustin Pop
  return py_stdout
161 2733df51 Iustin Pop
162 2733df51 Iustin Pop
-- * Arbitrary instances
163 2733df51 Iustin Pop
164 2733df51 Iustin Pop
-- | Defines a DNS name.
165 2733df51 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
166 2733df51 Iustin Pop
167 2733df51 Iustin Pop
instance Arbitrary DNSChar where
168 32f2e1e1 Iustin Pop
  arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
169 2733df51 Iustin Pop
170 2733df51 Iustin Pop
instance Show DNSChar where
171 2733df51 Iustin Pop
  show = show . dnsGetChar
172 2733df51 Iustin Pop
173 2733df51 Iustin Pop
-- | Generates a single name component.
174 5006418e Iustin Pop
genName :: Gen String
175 5006418e Iustin Pop
genName = do
176 086ad4cf Iustin Pop
  n <- choose (1, 16)
177 2733df51 Iustin Pop
  dn <- vector n
178 2733df51 Iustin Pop
  return (map dnsGetChar dn)
179 2733df51 Iustin Pop
180 2733df51 Iustin Pop
-- | Generates an entire FQDN.
181 5006418e Iustin Pop
genFQDN :: Gen String
182 5006418e Iustin Pop
genFQDN = do
183 2733df51 Iustin Pop
  ncomps <- choose (1, 4)
184 5006418e Iustin Pop
  names <- vectorOf ncomps genName
185 2733df51 Iustin Pop
  return $ intercalate "." names
186 2733df51 Iustin Pop
187 2733df51 Iustin Pop
-- | Combinator that generates a 'Maybe' using a sub-combinator.
188 5006418e Iustin Pop
genMaybe :: Gen a -> Gen (Maybe a)
189 4c49b965 Guido Trotter
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
190 305e174c Iustin Pop
191 305e174c Iustin Pop
-- | Defines a tag type.
192 305e174c Iustin Pop
newtype TagChar = TagChar { tagGetChar :: Char }
193 305e174c Iustin Pop
194 305e174c Iustin Pop
-- | All valid tag chars. This doesn't need to match _exactly_
195 305e174c Iustin Pop
-- Ganeti's own tag regex, just enough for it to be close.
196 5b11f8db Iustin Pop
tagChar :: String
197 305e174c Iustin Pop
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
198 305e174c Iustin Pop
199 305e174c Iustin Pop
instance Arbitrary TagChar where
200 32f2e1e1 Iustin Pop
  arbitrary = liftM TagChar $ elements tagChar
201 305e174c Iustin Pop
202 305e174c Iustin Pop
-- | Generates a tag
203 305e174c Iustin Pop
genTag :: Gen [TagChar]
204 305e174c Iustin Pop
genTag = do
205 305e174c Iustin Pop
  -- the correct value would be C.maxTagLen, but that's way too
206 305e174c Iustin Pop
  -- verbose in unittests, and at the moment I don't see any possible
207 305e174c Iustin Pop
  -- bugs with longer tags and the way we use tags in htools
208 305e174c Iustin Pop
  n <- choose (1, 10)
209 305e174c Iustin Pop
  vector n
210 305e174c Iustin Pop
211 305e174c Iustin Pop
-- | Generates a list of tags (correctly upper bounded).
212 305e174c Iustin Pop
genTags :: Gen [String]
213 305e174c Iustin Pop
genTags = do
214 305e174c Iustin Pop
  -- the correct value would be C.maxTagsPerObj, but per the comment
215 305e174c Iustin Pop
  -- in genTag, we don't use tags enough in htools to warrant testing
216 305e174c Iustin Pop
  -- such big values
217 305e174c Iustin Pop
  n <- choose (0, 10::Int)
218 305e174c Iustin Pop
  tags <- mapM (const genTag) [1..n]
219 305e174c Iustin Pop
  return $ map (map tagGetChar) tags
220 aed2325f Iustin Pop
221 aed2325f Iustin Pop
-- | Generates a fields list. This uses the same character set as a
222 aed2325f Iustin Pop
-- DNS name (just for simplicity).
223 5006418e Iustin Pop
genFields :: Gen [String]
224 5006418e Iustin Pop
genFields = do
225 aed2325f Iustin Pop
  n <- choose (1, 32)
226 5006418e Iustin Pop
  vectorOf n genName
227 e1ee7d5a Iustin Pop
228 e1ee7d5a Iustin Pop
-- | Generates a list of a given size with non-duplicate elements.
229 df8578fb Iustin Pop
genUniquesList :: (Eq a, Arbitrary a, Ord a) => Int -> Gen a -> Gen [a]
230 df8578fb Iustin Pop
genUniquesList cnt generator = do
231 df8578fb Iustin Pop
  set <- foldM (\set _ -> do
232 df8578fb Iustin Pop
                  newelem <- generator `suchThat` (`Set.notMember` set)
233 df8578fb Iustin Pop
                  return (Set.insert newelem set)) Set.empty [1..cnt]
234 df8578fb Iustin Pop
  return $ Set.toList set
235 e1ee7d5a Iustin Pop
236 e1ee7d5a Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
237 e1ee7d5a Iustin Pop
instance Arbitrary SmallRatio where
238 32f2e1e1 Iustin Pop
  arbitrary = liftM SmallRatio $ choose (0, 1)
239 63b068c1 Iustin Pop
240 2a8efa13 Iustin Pop
-- | Helper for 'genSet', declared separately due to type constraints.
241 2a8efa13 Iustin Pop
genSetHelper :: (Ord a) => [a] -> Maybe Int -> Gen (Set.Set a)
242 2a8efa13 Iustin Pop
genSetHelper candidates size = do
243 2a8efa13 Iustin Pop
  size' <- case size of
244 2a8efa13 Iustin Pop
             Nothing -> choose (0, length candidates)
245 2a8efa13 Iustin Pop
             Just s | s > length candidates ->
246 2a8efa13 Iustin Pop
                        error $ "Invalid size " ++ show s ++ ", maximum is " ++
247 2a8efa13 Iustin Pop
                                show (length candidates)
248 2a8efa13 Iustin Pop
                    | otherwise -> return s
249 2a8efa13 Iustin Pop
  foldM (\set _ -> do
250 2a8efa13 Iustin Pop
           newelem <- elements candidates `suchThat` (`Set.notMember` set)
251 2a8efa13 Iustin Pop
           return (Set.insert newelem set)) Set.empty [1..size']
252 2a8efa13 Iustin Pop
253 2a8efa13 Iustin Pop
-- | Generates a set of arbitrary elements.
254 2a8efa13 Iustin Pop
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
255 2a8efa13 Iustin Pop
genSet = genSetHelper [minBound..maxBound]
256 2a8efa13 Iustin Pop
257 0b288282 Helga Velroyen
-- | Generate an arbitrary IPv4 address in textual form (non empty).
258 0b288282 Helga Velroyen
genIp4Addr :: Gen NonEmptyString
259 0b288282 Helga Velroyen
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
260 0b288282 Helga Velroyen
261 0b288282 Helga Velroyen
-- | Generate an arbitrary IPv4 address in textual form.
262 0b288282 Helga Velroyen
genIp4AddrStr :: Gen String
263 0b288282 Helga Velroyen
genIp4AddrStr = do
264 0b288282 Helga Velroyen
  a <- choose (1::Int, 255)
265 0b288282 Helga Velroyen
  b <- choose (0::Int, 255)
266 0b288282 Helga Velroyen
  c <- choose (0::Int, 255)
267 0b288282 Helga Velroyen
  d <- choose (0::Int, 255)
268 0b288282 Helga Velroyen
  return $ intercalate "." (map show [a, b, c, d])
269 0b288282 Helga Velroyen
270 0b288282 Helga Velroyen
-- | Generates an arbitrary IPv4 address with a given netmask in textual form.
271 0b288282 Helga Velroyen
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
272 0b288282 Helga Velroyen
genIp4NetWithNetmask netmask = do
273 0b288282 Helga Velroyen
  ip <- genIp4AddrStr
274 0b288282 Helga Velroyen
  mkNonEmpty $ ip ++ "/" ++ show netmask
275 0b288282 Helga Velroyen
276 0b288282 Helga Velroyen
-- | Generate an arbitrary IPv4 network in textual form.
277 0b288282 Helga Velroyen
genIp4Net :: Gen NonEmptyString
278 0b288282 Helga Velroyen
genIp4Net = do
279 0b288282 Helga Velroyen
  netmask <- choose (8::Int, 30)
280 0b288282 Helga Velroyen
  genIp4NetWithNetmask netmask
281 0b288282 Helga Velroyen
282 0b288282 Helga Velroyen
-- | Helper function to compute the number of hosts in a network
283 0b288282 Helga Velroyen
-- given the netmask. (For IPv4 only.)
284 3a991f2d Iustin Pop
netmask2NumHosts :: Word8 -> Int
285 712da82f Helga Velroyen
netmask2NumHosts n = 2^(32-n)
286 0b288282 Helga Velroyen
287 0b288282 Helga Velroyen
-- | Generates an arbitrary IPv6 network address in textual form.
288 0b288282 Helga Velroyen
-- The generated address is not simpflified, e. g. an address like
289 0b288282 Helga Velroyen
-- "2607:f0d0:1002:0051:0000:0000:0000:0004" does not become
290 0b288282 Helga Velroyen
-- "2607:f0d0:1002:51::4"
291 0b288282 Helga Velroyen
genIp6Addr :: Gen String
292 0b288282 Helga Velroyen
genIp6Addr = do
293 0b288282 Helga Velroyen
  rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
294 0b288282 Helga Velroyen
  return $ intercalate ":" (map (`showHex` "") rawIp)
295 0b288282 Helga Velroyen
296 0b288282 Helga Velroyen
-- | Generates an arbitrary IPv6 network in textual form.
297 0b288282 Helga Velroyen
genIp6Net :: Gen String
298 0b288282 Helga Velroyen
genIp6Net = do
299 0b288282 Helga Velroyen
  netmask <- choose (8::Int, 126)
300 0b288282 Helga Velroyen
  ip <- genIp6Addr
301 0b288282 Helga Velroyen
  return $ ip ++ "/" ++ show netmask
302 0b288282 Helga Velroyen
303 2a8efa13 Iustin Pop
-- * Helper functions
304 2a8efa13 Iustin Pop
305 63b068c1 Iustin Pop
-- | Checks for serialisation idempotence.
306 63b068c1 Iustin Pop
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
307 63b068c1 Iustin Pop
testSerialisation a =
308 63b068c1 Iustin Pop
  case J.readJSON (J.showJSON a) of
309 63b068c1 Iustin Pop
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
310 63b068c1 Iustin Pop
    J.Ok a' -> a ==? a'
311 b9bdc10e Iustin Pop
312 b9bdc10e Iustin Pop
-- | Result to PropertyM IO.
313 93be1ced Iustin Pop
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
314 93be1ced Iustin Pop
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
315 b9bdc10e Iustin Pop
resultProp (BasicTypes.Ok  val) = return val
316 7b0476cf Michele Tartara
317 7b0476cf Michele Tartara
-- | Return the source directory of Ganeti.
318 7b0476cf Michele Tartara
getSourceDir :: IO FilePath
319 7b0476cf Michele Tartara
getSourceDir = catchJust (guard . isDoesNotExistError)
320 7b0476cf Michele Tartara
            (getEnv "TOP_SRCDIR")
321 7b0476cf Michele Tartara
            (const (return "."))
322 7b0476cf Michele Tartara
323 7b0476cf Michele Tartara
-- | Returns the path of a file in the test data directory, given its name.
324 7b0476cf Michele Tartara
testDataFilename :: String -> String -> IO FilePath
325 7b0476cf Michele Tartara
testDataFilename datadir name = do
326 7b0476cf Michele Tartara
        src <- getSourceDir
327 7b0476cf Michele Tartara
        return $ src ++ datadir ++ name
328 7b0476cf Michele Tartara
329 7b0476cf Michele Tartara
-- | Returns the content of the specified haskell test data file.
330 7b0476cf Michele Tartara
readTestData :: String -> IO String
331 7b0476cf Michele Tartara
readTestData filename = do
332 1c0f9d12 Iustin Pop
    name <- testDataFilename "/test/data/" filename
333 7b0476cf Michele Tartara
    readFile name
334 72747d91 Iustin Pop
335 72747d91 Iustin Pop
-- | Generate arbitrary values in the IO monad. This is a simple
336 72747d91 Iustin Pop
-- wrapper over 'sample''.
337 72747d91 Iustin Pop
genSample :: Gen a -> IO a
338 72747d91 Iustin Pop
genSample gen = do
339 72747d91 Iustin Pop
  values <- sample' gen
340 72747d91 Iustin Pop
  case values of
341 72747d91 Iustin Pop
    [] -> error "sample' returned an empty list of values??"
342 72747d91 Iustin Pop
    x:_ -> return x