Statistics
| Branch: | Tag: | Revision:

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

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