module Test.Ganeti.TestCommon
( maxMem
, maxDsk
, maxCpu
, maxSpindles
, maxVcpuRatio
, maxSpindleRatio
, maxNodes
, maxOpCodes
, (==?)
, (/=?)
, failTest
, passTest
, stableCover
, pythonCmd
, runPython
, checkPythonResult
, DNSChar(..)
, genPrintableAsciiChar
, genPrintableAsciiString
, genPrintableAsciiStringNE
, genPrintableByteString
, genName
, genFQDN
, genUUID
, genMaybe
, genSublist
, genMap
, genTags
, genFields
, genUniquesList
, SmallRatio(..)
, genSetHelper
, genSet
, genListSet
, genAndRestArguments
, genIPv4Address
, genIPv4Network
, genIp6Addr
, genIp6Net
, genOpCodesTagName
, genLuxiTagName
, netmask2NumHosts
, testSerialisation
, testArraySerialisation
, testDeserialisationFail
, resultProp
, readTestData
, genSample
, testParser
, genPropParser
, genNonNegative
, relativeError
, getTempFileName
, listOfUniqueBy
, counterexample
, cover'
) where
import Control.Exception (catchJust)
import Control.Monad
import Control.Monad.Fail (MonadFail, fail)
import Data.Attoparsec.Text (Parser, parseOnly)
import Data.List
import qualified Data.Map as M
import Data.Text (pack)
import Data.Word
import qualified Data.ByteString as BS
import qualified Data.ByteString.UTF8 as UTF8
#if !MIN_VERSION_QuickCheck(2,10,0)
import Data.Char (isPrint)
#endif
import qualified Data.Set as Set
import System.Directory (getTemporaryDirectory, removeFile)
import System.Environment (getEnv)
import System.Exit (ExitCode(..))
import System.IO (hClose, openTempFile)
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.JSON (ArrayObject(..))
import Ganeti.Objects (TagSet(..))
import Ganeti.Types
import Ganeti.Utils.Monad (unfoldrM)
instance MonadFail Gen where
fail = error "No monadfail instance"
instance MonadFail (Either String) where
fail x = Left x
instance Arbitrary TagSet where
arbitrary = (TagSet . Set.fromList) <$> genTags
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 = counterexample
("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 = counterexample
("Expected inequality, but got equality: '" ++
show x ++ "'.") (x /= y)
infix 3 /=?
failTest :: String -> Property
failTest msg = counterexample msg False
passTest :: Property
passTest = property True
cover' :: Testable prop => Double -> Bool -> String -> prop -> Property
#if MIN_VERSION_QuickCheck(2, 12, 0)
cover' = cover
#else
cover' p x = cover x (round p)
#endif
stableCover :: Testable prop => Bool -> Double -> String -> prop -> Property
stableCover p percent s prop =
let newlabel = "(stabilized to at least 10%) " ++ s
in forAll (frequency [(1, return True), (9, return False)]) $ \ basechance ->
cover' (10 + (percent * 9 / 10)) (basechance || p) newlabel prop
pythonCmd :: IO String
pythonCmd = catchJust (guard . isDoesNotExistError)
(getEnv "PYTHON") (const (return "python3"))
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
genPrintableAsciiChar :: Gen Char
genPrintableAsciiChar = choose ('\x20', '\x7e')
genPrintableAsciiString :: Gen String
genPrintableAsciiString = do
n <- choose (0, 40)
vectorOf n genPrintableAsciiChar
genPrintableAsciiStringNE :: Gen NonEmptyString
genPrintableAsciiStringNE = do
n <- choose (1, 40)
vectorOf n genPrintableAsciiChar >>= mkNonEmpty
genPrintableByteString :: Gen BS.ByteString
#if MIN_VERSION_QuickCheck(2, 10, 0)
genPrintableByteString = fmap (UTF8.fromString . getPrintableString) arbitrary
#else
genPrintableByteString =
fmap UTF8.fromString $ listOf (arbitrary `suchThat` isPrint)
#endif
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) ]
genSublist :: [a] -> Gen [a]
genSublist xs = choose (0, l) >>= g xs l
where
l = length xs
g _ _ 0 = return []
g [] _ _ = return []
g ys n k | k == n = return ys
g (y:ys) n k = frequency [ (k, liftM (y :) (g ys (n 1) (k 1)))
, (n k, g ys (n 1) k)
]
genMap :: (Ord k, Ord v) => Gen k -> Gen v -> Gen (M.Map k v)
genMap kg vg = M.fromList <$> listOf ((,) <$> kg <*> vg)
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]
genListSet :: (Ord a, Bounded a, Enum a) => Maybe Int
-> Gen (BasicTypes.ListSet a)
genListSet is = BasicTypes.ListSet <$> genSet is
genAndRestArguments :: Gen (M.Map String J.JSValue)
genAndRestArguments = do
n <- choose (0::Int, 10)
let oneParam _ = do
name <- choose (15 ::Int, 25)
>>= flip vectorOf (elements tagChar)
intvalue <- arbitrary
value <- oneof [ J.JSString . J.toJSString <$> genName
, return $ J.showJSON (intvalue :: Int)
]
return (name, value)
M.fromList `liftM` mapM oneParam [1..n]
genIPv4 :: Gen String
genIPv4 = 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]
genIPv4Address :: Gen IPv4Address
genIPv4Address = mkIPv4Address =<< genIPv4
genIPv4AddrRange :: Gen String
genIPv4AddrRange = do
pfxLen <- choose (8::Int, 30)
addr <- choose(1::Int, 2^pfxLen1)
let hostLen = 32 pfxLen
net = addr * 2^hostLen
netBytes = [(net `div` 2^x) `mod` 256 | x <- [24::Int, 16, 8, 0]]
return $ intercalate "." (map show netBytes) ++ "/" ++ show pfxLen
genIPv4Network :: Gen IPv4Network
genIPv4Network = mkIPv4Network =<< genIPv4AddrRange
netmask2NumHosts :: Word8 -> Int
netmask2NumHosts n = 2^(32n)
genIp6Addr :: Gen String
genIp6Addr = do
rawIp <- vectorOf 8 $ choose (0::Integer, 65535)
return $ intercalate ":" (map (`showHex` "") rawIp)
ip6AddressFromNumber :: Integer -> [Char]
ip6AddressFromNumber ipInt =
let chunksOf :: Int -> [a] -> [[a]]
chunksOf _ [] = []
chunksOf n lst = take n lst : (chunksOf n $ drop n lst)
lPadTrim :: Int -> a -> [a] -> [a]
lPadTrim n p lst
| length lst < n = lPadTrim n p $ p : lst
| otherwise = take n lst
rawIp = lPadTrim 32 '0' $ (`showHex` "") ipInt
in intercalate ":" $ chunksOf 4 rawIp
genIp6Net :: Gen String
genIp6Net = do
netmask <- choose (8::Int, 126)
raw_ip <- (* 2^(128netmask)) <$> choose(1::Integer, 2^netmask1)
return $ ip6AddressFromNumber raw_ip ++ "/" ++ show netmask
genOpCodesTagName :: TagKind -> Gen (Maybe String)
genOpCodesTagName TagKindCluster = return Nothing
genOpCodesTagName _ = Just <$> genFQDN
genLuxiTagName :: TagKind -> Gen String
genLuxiTagName TagKindCluster = return ""
genLuxiTagName _ = genFQDN
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'
testArraySerialisation :: (Eq a, Show a, ArrayObject a) => a -> Property
testArraySerialisation a =
case fromJSArray (toJSArray a) of
J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
J.Ok a' -> a ==? a'
testDeserialisationFail :: (Eq a, Show a, J.JSON a)
=> a -> J.JSValue -> Property
testDeserialisationFail a val =
case liftM (`asTypeOf` a) $ J.readJSON val of
J.Error _ -> passTest
J.Ok x -> failTest $ "Parsed invalid value " ++ show val ++
" to: " ++ show x
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 fromEnum (arbitrary::Gen (Test.QuickCheck.NonNegative Int))
relativeError :: Double -> Double -> Double
relativeError d1 d2 =
let delta = abs $ d1 d2
a1 = abs d1
a2 = abs d2
greatest = max a1 a2
in if delta == 0
then 0
else delta / greatest
getTempFileName :: String -> IO FilePath
getTempFileName filename = do
tempdir <- getTemporaryDirectory
(fpath, handle) <- openTempFile tempdir filename
_ <- hClose handle
removeFile fpath
return fpath
listOfUniqueBy :: (Ord b) => Gen a -> (a -> b) -> [a] -> Gen [a]
listOfUniqueBy gen keyFun forbidden = do
let keysOf = Set.fromList . map keyFun
k <- sized $ \n -> choose (0, n)
flip unfoldrM (0, keysOf forbidden) $ \(i, usedKeys) ->
if i == k
then return Nothing
else do
x <- gen `suchThat` ((`Set.notMember` usedKeys) . keyFun)
return $ Just (x, (i + 1, Set.insert (keyFun x) usedKeys))