Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / TestCommon.hs @ 61899e64

History | View | Annotate | Download (6.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 2733df51 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 aed2325f Iustin Pop
import qualified Test.HUnit as HUnit
33 2733df51 Iustin Pop
import Test.QuickCheck
34 b9bdc10e Iustin Pop
import Test.QuickCheck.Monadic
35 63b068c1 Iustin Pop
import qualified Text.JSON as J
36 aed2325f Iustin Pop
import System.Environment (getEnv)
37 aed2325f Iustin Pop
import System.Exit (ExitCode(..))
38 aed2325f Iustin Pop
import System.IO.Error (isDoesNotExistError)
39 aed2325f Iustin Pop
import System.Process (readProcessWithExitCode)
40 2733df51 Iustin Pop
41 b9bdc10e Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
42 b9bdc10e Iustin Pop
43 2733df51 Iustin Pop
-- * Constants
44 2733df51 Iustin Pop
45 2733df51 Iustin Pop
-- | Maximum memory (1TiB, somewhat random value).
46 2733df51 Iustin Pop
maxMem :: Int
47 2733df51 Iustin Pop
maxMem = 1024 * 1024
48 2733df51 Iustin Pop
49 2733df51 Iustin Pop
-- | Maximum disk (8TiB, somewhat random value).
50 2733df51 Iustin Pop
maxDsk :: Int
51 2733df51 Iustin Pop
maxDsk = 1024 * 1024 * 8
52 2733df51 Iustin Pop
53 2733df51 Iustin Pop
-- | Max CPUs (1024, somewhat random value).
54 2733df51 Iustin Pop
maxCpu :: Int
55 2733df51 Iustin Pop
maxCpu = 1024
56 2733df51 Iustin Pop
57 2733df51 Iustin Pop
-- | Max vcpu ratio (random value).
58 2733df51 Iustin Pop
maxVcpuRatio :: Double
59 2733df51 Iustin Pop
maxVcpuRatio = 1024.0
60 2733df51 Iustin Pop
61 2733df51 Iustin Pop
-- | Max spindle ratio (random value).
62 2733df51 Iustin Pop
maxSpindleRatio :: Double
63 2733df51 Iustin Pop
maxSpindleRatio = 1024.0
64 2733df51 Iustin Pop
65 2733df51 Iustin Pop
-- | Max nodes, used just to limit arbitrary instances for smaller
66 2733df51 Iustin Pop
-- opcode definitions (e.g. list of nodes in OpTestDelay).
67 2733df51 Iustin Pop
maxNodes :: Int
68 2733df51 Iustin Pop
maxNodes = 32
69 2733df51 Iustin Pop
70 2733df51 Iustin Pop
-- | Max opcodes or jobs in a submit job and submit many jobs.
71 2733df51 Iustin Pop
maxOpCodes :: Int
72 2733df51 Iustin Pop
maxOpCodes = 16
73 2733df51 Iustin Pop
74 2733df51 Iustin Pop
-- * Helper functions
75 2733df51 Iustin Pop
76 41eb900e Iustin Pop
-- | Checks for equality with proper annotation. The first argument is
77 41eb900e Iustin Pop
-- the computed value, the second one the expected value.
78 2733df51 Iustin Pop
(==?) :: (Show a, Eq a) => a -> a -> Property
79 2733df51 Iustin Pop
(==?) x y = printTestCase
80 41eb900e Iustin Pop
            ("Expected equality, but got mismatch\nexpected: " ++
81 a309a3b4 Iustin Pop
             show y ++ "\n but got: " ++ show x) (x == y)
82 2733df51 Iustin Pop
infix 3 ==?
83 2733df51 Iustin Pop
84 41eb900e Iustin Pop
-- | Checks for inequality with proper annotation. The first argument
85 41eb900e Iustin Pop
-- is the computed value, the second one the expected (not equal)
86 41eb900e Iustin Pop
-- value.
87 dddb2bc9 Helga Velroyen
(/=?) :: (Show a, Eq a) => a -> a -> Property
88 dddb2bc9 Helga Velroyen
(/=?) x y = printTestCase
89 dddb2bc9 Helga Velroyen
            ("Expected inequality, but got equality: '" ++
90 dddb2bc9 Helga Velroyen
             show x ++ "'.") (x /= y)
91 dddb2bc9 Helga Velroyen
infix 3 /=?
92 dddb2bc9 Helga Velroyen
93 2733df51 Iustin Pop
-- | Show a message and fail the test.
94 2733df51 Iustin Pop
failTest :: String -> Property
95 2733df51 Iustin Pop
failTest msg = printTestCase msg False
96 2733df51 Iustin Pop
97 2e0bb81d Iustin Pop
-- | A 'True' property.
98 2e0bb81d Iustin Pop
passTest :: Property
99 2e0bb81d Iustin Pop
passTest = property True
100 2e0bb81d Iustin Pop
101 aed2325f Iustin Pop
-- | Return the python binary to use. If the PYTHON environment
102 aed2325f Iustin Pop
-- variable is defined, use its value, otherwise use just \"python\".
103 aed2325f Iustin Pop
pythonCmd :: IO String
104 aed2325f Iustin Pop
pythonCmd = catchJust (guard . isDoesNotExistError)
105 aed2325f Iustin Pop
            (getEnv "PYTHON") (const (return "python"))
106 aed2325f Iustin Pop
107 aed2325f Iustin Pop
-- | Run Python with an expression, returning the exit code, standard
108 aed2325f Iustin Pop
-- output and error.
109 aed2325f Iustin Pop
runPython :: String -> String -> IO (ExitCode, String, String)
110 aed2325f Iustin Pop
runPython expr stdin = do
111 aed2325f Iustin Pop
  py_binary <- pythonCmd
112 aed2325f Iustin Pop
  readProcessWithExitCode py_binary ["-c", expr] stdin
113 aed2325f Iustin Pop
114 aed2325f Iustin Pop
-- | Check python exit code, and fail via HUnit assertions if
115 aed2325f Iustin Pop
-- non-zero. Otherwise, return the standard output.
116 aed2325f Iustin Pop
checkPythonResult :: (ExitCode, String, String) -> IO String
117 aed2325f Iustin Pop
checkPythonResult (py_code, py_stdout, py_stderr) = do
118 aed2325f Iustin Pop
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
119 aed2325f Iustin Pop
       ExitSuccess py_code
120 aed2325f Iustin Pop
  return py_stdout
121 2733df51 Iustin Pop
122 2733df51 Iustin Pop
-- * Arbitrary instances
123 2733df51 Iustin Pop
124 2733df51 Iustin Pop
-- | Defines a DNS name.
125 2733df51 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
126 2733df51 Iustin Pop
127 2733df51 Iustin Pop
instance Arbitrary DNSChar where
128 2733df51 Iustin Pop
  arbitrary = do
129 2733df51 Iustin Pop
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
130 2733df51 Iustin Pop
    return (DNSChar x)
131 2733df51 Iustin Pop
132 2733df51 Iustin Pop
instance Show DNSChar where
133 2733df51 Iustin Pop
  show = show . dnsGetChar
134 2733df51 Iustin Pop
135 2733df51 Iustin Pop
-- | Generates a single name component.
136 2733df51 Iustin Pop
getName :: Gen String
137 2733df51 Iustin Pop
getName = do
138 2733df51 Iustin Pop
  n <- choose (1, 64)
139 2733df51 Iustin Pop
  dn <- vector n
140 2733df51 Iustin Pop
  return (map dnsGetChar dn)
141 2733df51 Iustin Pop
142 2733df51 Iustin Pop
-- | Generates an entire FQDN.
143 2733df51 Iustin Pop
getFQDN :: Gen String
144 2733df51 Iustin Pop
getFQDN = do
145 2733df51 Iustin Pop
  ncomps <- choose (1, 4)
146 2733df51 Iustin Pop
  names <- vectorOf ncomps getName
147 2733df51 Iustin Pop
  return $ intercalate "." names
148 2733df51 Iustin Pop
149 2733df51 Iustin Pop
-- | Combinator that generates a 'Maybe' using a sub-combinator.
150 2733df51 Iustin Pop
getMaybe :: Gen a -> Gen (Maybe a)
151 2733df51 Iustin Pop
getMaybe subgen = do
152 2733df51 Iustin Pop
  bool <- arbitrary
153 2733df51 Iustin Pop
  if bool
154 2733df51 Iustin Pop
    then Just <$> subgen
155 2733df51 Iustin Pop
    else return Nothing
156 305e174c Iustin Pop
157 305e174c Iustin Pop
-- | Defines a tag type.
158 305e174c Iustin Pop
newtype TagChar = TagChar { tagGetChar :: Char }
159 305e174c Iustin Pop
160 305e174c Iustin Pop
-- | All valid tag chars. This doesn't need to match _exactly_
161 305e174c Iustin Pop
-- Ganeti's own tag regex, just enough for it to be close.
162 5b11f8db Iustin Pop
tagChar :: String
163 305e174c Iustin Pop
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
164 305e174c Iustin Pop
165 305e174c Iustin Pop
instance Arbitrary TagChar where
166 305e174c Iustin Pop
  arbitrary = do
167 305e174c Iustin Pop
    c <- elements tagChar
168 305e174c Iustin Pop
    return (TagChar c)
169 305e174c Iustin Pop
170 305e174c Iustin Pop
-- | Generates a tag
171 305e174c Iustin Pop
genTag :: Gen [TagChar]
172 305e174c Iustin Pop
genTag = do
173 305e174c Iustin Pop
  -- the correct value would be C.maxTagLen, but that's way too
174 305e174c Iustin Pop
  -- verbose in unittests, and at the moment I don't see any possible
175 305e174c Iustin Pop
  -- bugs with longer tags and the way we use tags in htools
176 305e174c Iustin Pop
  n <- choose (1, 10)
177 305e174c Iustin Pop
  vector n
178 305e174c Iustin Pop
179 305e174c Iustin Pop
-- | Generates a list of tags (correctly upper bounded).
180 305e174c Iustin Pop
genTags :: Gen [String]
181 305e174c Iustin Pop
genTags = do
182 305e174c Iustin Pop
  -- the correct value would be C.maxTagsPerObj, but per the comment
183 305e174c Iustin Pop
  -- in genTag, we don't use tags enough in htools to warrant testing
184 305e174c Iustin Pop
  -- such big values
185 305e174c Iustin Pop
  n <- choose (0, 10::Int)
186 305e174c Iustin Pop
  tags <- mapM (const genTag) [1..n]
187 305e174c Iustin Pop
  return $ map (map tagGetChar) tags
188 aed2325f Iustin Pop
189 aed2325f Iustin Pop
-- | Generates a fields list. This uses the same character set as a
190 aed2325f Iustin Pop
-- DNS name (just for simplicity).
191 aed2325f Iustin Pop
getFields :: Gen [String]
192 aed2325f Iustin Pop
getFields = do
193 aed2325f Iustin Pop
  n <- choose (1, 32)
194 aed2325f Iustin Pop
  vectorOf n getName
195 e1ee7d5a Iustin Pop
196 e1ee7d5a Iustin Pop
-- | Generates a list of a given size with non-duplicate elements.
197 e1ee7d5a Iustin Pop
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
198 e1ee7d5a Iustin Pop
genUniquesList cnt =
199 e1ee7d5a Iustin Pop
  foldM (\lst _ -> do
200 e1ee7d5a Iustin Pop
           newelem <- arbitrary `suchThat` (`notElem` lst)
201 e1ee7d5a Iustin Pop
           return (newelem:lst)) [] [1..cnt]
202 e1ee7d5a Iustin Pop
203 e1ee7d5a Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
204 e1ee7d5a Iustin Pop
instance Arbitrary SmallRatio where
205 e1ee7d5a Iustin Pop
  arbitrary = do
206 e1ee7d5a Iustin Pop
    v <- choose (0, 1)
207 e1ee7d5a Iustin Pop
    return $ SmallRatio v
208 63b068c1 Iustin Pop
209 63b068c1 Iustin Pop
-- | Checks for serialisation idempotence.
210 63b068c1 Iustin Pop
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
211 63b068c1 Iustin Pop
testSerialisation a =
212 63b068c1 Iustin Pop
  case J.readJSON (J.showJSON a) of
213 63b068c1 Iustin Pop
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
214 63b068c1 Iustin Pop
    J.Ok a' -> a ==? a'
215 b9bdc10e Iustin Pop
216 b9bdc10e Iustin Pop
-- | Result to PropertyM IO.
217 93be1ced Iustin Pop
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
218 93be1ced Iustin Pop
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
219 b9bdc10e Iustin Pop
resultProp (BasicTypes.Ok  val) = return val