Statistics
| Branch: | Tag: | Revision:

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

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