Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / TestCommon.hs @ 63b068c1

History | View | Annotate | Download (5.6 kB)

1
{-| Unittest helpers for ganeti-htools.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Test.Ganeti.TestCommon where
27

    
28
import Control.Applicative
29
import Control.Exception (catchJust)
30
import Control.Monad
31
import Data.List
32
import qualified Test.HUnit as HUnit
33
import Test.QuickCheck
34
import qualified Text.JSON as J
35
import System.Environment (getEnv)
36
import System.Exit (ExitCode(..))
37
import System.IO.Error (isDoesNotExistError)
38
import System.Process (readProcessWithExitCode)
39

    
40
-- * Constants
41

    
42
-- | Maximum memory (1TiB, somewhat random value).
43
maxMem :: Int
44
maxMem = 1024 * 1024
45

    
46
-- | Maximum disk (8TiB, somewhat random value).
47
maxDsk :: Int
48
maxDsk = 1024 * 1024 * 8
49

    
50
-- | Max CPUs (1024, somewhat random value).
51
maxCpu :: Int
52
maxCpu = 1024
53

    
54
-- | Max vcpu ratio (random value).
55
maxVcpuRatio :: Double
56
maxVcpuRatio = 1024.0
57

    
58
-- | Max spindle ratio (random value).
59
maxSpindleRatio :: Double
60
maxSpindleRatio = 1024.0
61

    
62
-- | Max nodes, used just to limit arbitrary instances for smaller
63
-- opcode definitions (e.g. list of nodes in OpTestDelay).
64
maxNodes :: Int
65
maxNodes = 32
66

    
67
-- | Max opcodes or jobs in a submit job and submit many jobs.
68
maxOpCodes :: Int
69
maxOpCodes = 16
70

    
71
-- * Helper functions
72

    
73
-- | Checks for equality with proper annotation.
74
(==?) :: (Show a, Eq a) => a -> a -> Property
75
(==?) x y = printTestCase
76
            ("Expected equality, but '" ++
77
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
78
infix 3 ==?
79

    
80
-- | Show a message and fail the test.
81
failTest :: String -> Property
82
failTest msg = printTestCase msg False
83

    
84
-- | Return the python binary to use. If the PYTHON environment
85
-- variable is defined, use its value, otherwise use just \"python\".
86
pythonCmd :: IO String
87
pythonCmd = catchJust (guard . isDoesNotExistError)
88
            (getEnv "PYTHON") (const (return "python"))
89

    
90
-- | Run Python with an expression, returning the exit code, standard
91
-- output and error.
92
runPython :: String -> String -> IO (ExitCode, String, String)
93
runPython expr stdin = do
94
  py_binary <- pythonCmd
95
  readProcessWithExitCode py_binary ["-c", expr] stdin
96

    
97
-- | Check python exit code, and fail via HUnit assertions if
98
-- non-zero. Otherwise, return the standard output.
99
checkPythonResult :: (ExitCode, String, String) -> IO String
100
checkPythonResult (py_code, py_stdout, py_stderr) = do
101
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
102
       ExitSuccess py_code
103
  return py_stdout
104

    
105
-- * Arbitrary instances
106

    
107
-- | Defines a DNS name.
108
newtype DNSChar = DNSChar { dnsGetChar::Char }
109

    
110
instance Arbitrary DNSChar where
111
  arbitrary = do
112
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
113
    return (DNSChar x)
114

    
115
instance Show DNSChar where
116
  show = show . dnsGetChar
117

    
118
-- | Generates a single name component.
119
getName :: Gen String
120
getName = do
121
  n <- choose (1, 64)
122
  dn <- vector n
123
  return (map dnsGetChar dn)
124

    
125
-- | Generates an entire FQDN.
126
getFQDN :: Gen String
127
getFQDN = do
128
  ncomps <- choose (1, 4)
129
  names <- vectorOf ncomps getName
130
  return $ intercalate "." names
131

    
132
-- | Combinator that generates a 'Maybe' using a sub-combinator.
133
getMaybe :: Gen a -> Gen (Maybe a)
134
getMaybe subgen = do
135
  bool <- arbitrary
136
  if bool
137
    then Just <$> subgen
138
    else return Nothing
139

    
140
-- | Defines a tag type.
141
newtype TagChar = TagChar { tagGetChar :: Char }
142

    
143
-- | All valid tag chars. This doesn't need to match _exactly_
144
-- Ganeti's own tag regex, just enough for it to be close.
145
tagChar :: [Char]
146
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
147

    
148
instance Arbitrary TagChar where
149
  arbitrary = do
150
    c <- elements tagChar
151
    return (TagChar c)
152

    
153
-- | Generates a tag
154
genTag :: Gen [TagChar]
155
genTag = do
156
  -- the correct value would be C.maxTagLen, but that's way too
157
  -- verbose in unittests, and at the moment I don't see any possible
158
  -- bugs with longer tags and the way we use tags in htools
159
  n <- choose (1, 10)
160
  vector n
161

    
162
-- | Generates a list of tags (correctly upper bounded).
163
genTags :: Gen [String]
164
genTags = do
165
  -- the correct value would be C.maxTagsPerObj, but per the comment
166
  -- in genTag, we don't use tags enough in htools to warrant testing
167
  -- such big values
168
  n <- choose (0, 10::Int)
169
  tags <- mapM (const genTag) [1..n]
170
  return $ map (map tagGetChar) tags
171

    
172
-- | Generates a fields list. This uses the same character set as a
173
-- DNS name (just for simplicity).
174
getFields :: Gen [String]
175
getFields = do
176
  n <- choose (1, 32)
177
  vectorOf n getName
178

    
179
-- | Generates a list of a given size with non-duplicate elements.
180
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
181
genUniquesList cnt =
182
  foldM (\lst _ -> do
183
           newelem <- arbitrary `suchThat` (`notElem` lst)
184
           return (newelem:lst)) [] [1..cnt]
185

    
186
newtype SmallRatio = SmallRatio Double deriving Show
187
instance Arbitrary SmallRatio where
188
  arbitrary = do
189
    v <- choose (0, 1)
190
    return $ SmallRatio v
191

    
192
-- | Checks for serialisation idempotence.
193
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
194
testSerialisation a =
195
  case J.readJSON (J.showJSON a) of
196
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
197
    J.Ok a' -> a ==? a'