Statistics
| Branch: | Tag: | Revision:

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

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