Statistics
| Branch: | Tag: | Revision:

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

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