module Test.Ganeti.TestCommon
( maxMem
, maxDsk
, maxCpu
, maxSpindles
, maxVcpuRatio
, maxSpindleRatio
, maxNodes
, maxOpCodes
, (==?)
, (/=?)
, failTest
, passTest
, pythonCmd
, runPython
, checkPythonResult
, DNSChar(..)
, genName
, genFQDN
, genUUID
, genMaybe
, genTags
, genFields
, genUniquesList
, SmallRatio(..)
, genSetHelper
, genSet
, genIp4AddrStr
, genIp4Addr
, genIp4NetWithNetmask
, genIp4Net
, genIp6Addr
, genIp6Net
, netmask2NumHosts
, testSerialisation
, resultProp
, readTestData
, genSample
, testParser
, genPropParser
, genNonNegative
) where
import Control.Applicative
import Control.Exception (catchJust)
import Control.Monad
import Data.Attoparsec.Text (Parser, parseOnly)
import Data.List
import Data.Text (pack)
import Data.Word
import qualified Data.Set as Set
import System.Environment (getEnv)
import System.Exit (ExitCode(..))
import System.IO.Error (isDoesNotExistError)
import System.Process (readProcessWithExitCode)
import qualified Test.HUnit as HUnit
import Test.QuickCheck
import Test.QuickCheck.Monadic
import qualified Text.JSON as J
import Numeric
import qualified Ganeti.BasicTypes as BasicTypes
import Ganeti.Types
maxMem :: Int
maxMem = 1024 * 1024
maxDsk :: Int
maxDsk = 1024 * 1024 * 8
maxCpu :: Int
maxCpu = 1024
maxSpindles :: Int
maxSpindles = 1024
maxVcpuRatio :: Double
maxVcpuRatio = 1024.0
maxSpindleRatio :: Double
maxSpindleRatio = 1024.0
maxNodes :: Int
maxNodes = 32
maxOpCodes :: Int
maxOpCodes = 16
(==?) :: (Show a, Eq a) => a -> a -> Property
(==?) x y = printTestCase
("Expected equality, but got mismatch\nexpected: " ++
show y ++ "\n but got: " ++ show x) (x == y)
infix 3 ==?
(/=?) :: (Show a, Eq a) => a -> a -> Property
(/=?) x y = printTestCase
("Expected inequality, but got equality: '" ++
show x ++ "'.") (x /= y)
infix 3 /=?
failTest :: String -> Property
failTest msg = printTestCase msg False
passTest :: Property
passTest = property True
pythonCmd :: IO String
pythonCmd = catchJust (guard . isDoesNotExistError)
(getEnv "PYTHON") (const (return "python"))
runPython :: String -> String -> IO (ExitCode, String, String)
runPython expr stdin = do
py_binary <- pythonCmd
readProcessWithExitCode py_binary ["-c", expr] stdin
checkPythonResult :: (ExitCode, String, String) -> IO String
checkPythonResult (py_code, py_stdout, py_stderr) = do
HUnit.assertEqual ("python exited with error: " ++ py_stderr)
ExitSuccess py_code
return py_stdout
newtype DNSChar = DNSChar { dnsGetChar::Char }
instance Arbitrary DNSChar where
arbitrary = liftM DNSChar $ elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
instance Show DNSChar where
show = show . dnsGetChar
genName :: Gen String
genName = do
n <- choose (1, 16)
dn <- vector n
return (map dnsGetChar dn)
genFQDN :: Gen String
genFQDN = do
ncomps <- choose (1, 4)
names <- vectorOf ncomps genName
return $ intercalate "." names
genUUID :: Gen String
genUUID = do
c1 <- vector 6
c2 <- vector 4
c3 <- vector 4
c4 <- vector 4
c5 <- vector 4
c6 <- vector 4
c7 <- vector 6
return $ map dnsGetChar c1 ++ "-" ++ map dnsGetChar c2 ++ "-" ++
map dnsGetChar c3 ++ "-" ++ map dnsGetChar c4 ++ "-" ++
map dnsGetChar c5 ++ "-" ++ map dnsGetChar c6 ++ "-" ++
map dnsGetChar c7
genMaybe :: Gen a -> Gen (Maybe a)
genMaybe subgen = frequency [ (1, pure Nothing), (3, Just <$> subgen) ]
newtype TagChar = TagChar { tagGetChar :: Char }
tagChar :: String
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
instance Arbitrary TagChar where
arbitrary = liftM TagChar $ elements tagChar
genTag :: Gen [TagChar]
genTag = do
n <- choose (1, 10)
vector n
genTags :: Gen [String]
genTags = do
n <- choose (0, 10::Int)
tags <- mapM (const genTag) [1..n]
return $ map (map tagGetChar) tags
genFields :: Gen [String]
genFields = do
n <- choose (1, 32)
vectorOf n genName
genUniquesList :: (Eq a, Arbitrary a, Ord a) => Int -> Gen a -> Gen [a]
genUniquesList cnt generator = do
set <- foldM (\set _ -> do
newelem <- generator `suchThat` (`Set.notMember` set)
return (Set.insert newelem set)) Set.empty [1..cnt]
return $ Set.toList set
newtype SmallRatio = SmallRatio Double deriving Show
instance Arbitrary SmallRatio where
arbitrary = liftM SmallRatio $ choose (0, 1)
genSetHelper :: (Ord a) => [a] -> Maybe Int -> Gen (Set.Set a)
genSetHelper candidates size = do
size' <- case size of
Nothing -> choose (0, length candidates)
Just s | s > length candidates ->
error $ "Invalid size " ++ show s ++ ", maximum is " ++
show (length candidates)
| otherwise -> return s
foldM (\set _ -> do
newelem <- elements candidates `suchThat` (`Set.notMember` set)
return (Set.insert newelem set)) Set.empty [1..size']
genSet :: (Ord a, Bounded a, Enum a) => Maybe Int -> Gen (Set.Set a)
genSet = genSetHelper [minBound..maxBound]
genIp4Addr :: Gen NonEmptyString
genIp4Addr = genIp4AddrStr >>= mkNonEmpty
genIp4AddrStr :: Gen String
genIp4AddrStr = do
a <- choose (1::Int, 255)
b <- choose (0::Int, 255)
c <- choose (0::Int, 255)
d <- choose (0::Int, 255)
return $ intercalate "." (map show [a, b, c, d])
genIp4NetWithNetmask :: Int -> Gen NonEmptyString
genIp4NetWithNetmask netmask = do
ip <- genIp4AddrStr
mkNonEmpty $ ip ++ "/" ++ show netmask
genIp4Net :: Gen NonEmptyString
genIp4Net = do
netmask <- choose (8::Int, 30)
genIp4NetWithNetmask netmask
netmask2NumHosts :: Word8 -> Int
netmask2NumHosts n = 2^(32n)
genIp6Addr :: Gen String
genIp6Addr = do
rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
return $ intercalate ":" (map (`showHex` "") rawIp)
genIp6Net :: Gen String
genIp6Net = do
netmask <- choose (8::Int, 126)
ip <- genIp6Addr
return $ ip ++ "/" ++ show netmask
testSerialisation :: (Eq a, Show a, J.JSON a) => a -> Property
testSerialisation a =
case J.readJSON (J.showJSON a) of
J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
J.Ok a' -> a ==? a'
resultProp :: (Show a) => BasicTypes.GenericResult a b -> PropertyM IO b
resultProp (BasicTypes.Bad err) = stop . failTest $ show err
resultProp (BasicTypes.Ok val) = return val
getSourceDir :: IO FilePath
getSourceDir = catchJust (guard . isDoesNotExistError)
(getEnv "TOP_SRCDIR")
(const (return "."))
testDataFilename :: String -> String -> IO FilePath
testDataFilename datadir name = do
src <- getSourceDir
return $ src ++ datadir ++ name
readTestData :: String -> IO String
readTestData filename = do
name <- testDataFilename "/test/data/" filename
readFile name
genSample :: Gen a -> IO a
genSample gen = do
values <- sample' gen
case values of
[] -> error "sample' returned an empty list of values??"
x:_ -> return x
testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
testParser parser fileName expectedContent = do
fileContent <- readTestData fileName
case parseOnly parser $ pack fileContent of
Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
Right obtained -> HUnit.assertEqual fileName expectedContent obtained
genPropParser :: (Show a, Eq a) => Parser a -> String -> a -> Property
genPropParser parser s expected =
case parseOnly parser $ pack s of
Left msg -> failTest $ "Parsing failed: " ++ msg
Right obtained -> expected ==? obtained
genNonNegative :: Gen Int
genNonNegative =
fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))