Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestCommon.hs @ 688f35e6

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