module Test.Ganeti.Hypervisor.Xen.XmParser
( testHypervisor_Xen_XmParser
) where
import Test.HUnit
import Test.QuickCheck as QuickCheck hiding (Result)
import Test.Ganeti.TestHelper
import Test.Ganeti.TestCommon
import Control.Monad (liftM)
import qualified Data.Attoparsec.Text as A
import Data.Text (pack)
import Data.Char
import qualified Data.Map as Map
import Text.Printf
import Ganeti.Hypervisor.Xen.Types
import Ganeti.Hypervisor.Xen.XmParser
genConfig :: Int -> Gen LispConfig
genConfig 0 =
frequency [ (5, liftM LCString (genName `suchThat` (not . canBeNumber)))
, (5, liftM LCDouble arbitrary)
]
genConfig n =
frequency [ (5, liftM LCString (resize n genName `suchThat`
(not . canBeNumber)))
, (5, liftM LCDouble arbitrary)
, (1, liftM LCList (choose (1, n) >>=
(\n' -> vectorOf n' (genConfig $ n `div` n'))))
]
instance Arbitrary LispConfig where
arbitrary = sized genConfig
canBeNumber :: String -> Bool
canBeNumber [] = False
canBeNumber [c] = canBeNumberChar c
canBeNumber (c:xs) = canBeNumberChar c && canBeNumber xs
canBeNumberChar :: Char -> Bool
canBeNumberChar c = isDigit c || (c `elem` "eE-")
instance Arbitrary UptimeInfo where
arbitrary = do
name <- genFQDN
NonNegative idNum <- arbitrary :: Gen (NonNegative Int)
NonNegative days <- arbitrary :: Gen (NonNegative Int)
hours <- choose (0, 23) :: Gen Int
mins <- choose (0, 59) :: Gen Int
secs <- choose (0, 59) :: Gen Int
let uptime :: String
uptime =
if days /= 0
then printf "%d days, %d:%d:%d" days hours mins secs
else printf "%d:%d:%d" hours mins secs
return $ UptimeInfo name idNum uptime
testDomain :: String -> Map.Map String Domain -> Assertion
testDomain fileName expectedContent = do
fileContent <- readTestData fileName
case A.parseOnly xmListParser $ pack fileContent of
Left msg -> assertFailure $ "Parsing failed: " ++ msg
Right obtained -> assertEqual fileName expectedContent obtained
testUptimeInfo :: String -> Map.Map Int UptimeInfo -> Assertion
testUptimeInfo fileName expectedContent = do
fileContent <- readTestData fileName
case A.parseOnly xmUptimeParser $ pack fileContent of
Left msg -> assertFailure $ "Parsing failed: " ++ msg
Right obtained -> assertEqual fileName expectedContent obtained
isAlmostEqual :: LispConfig -> LispConfig -> Property
isAlmostEqual (LCList c1) (LCList c2) =
(length c1 ==? length c2) .&&.
conjoin (zipWith isAlmostEqual c1 c2)
isAlmostEqual (LCString s1) (LCString s2) = s1 ==? s2
isAlmostEqual (LCDouble d1) (LCDouble d2) = counterexample msg $ rel <= 1e-12
where rel = relativeError d1 d2
msg = "Relative error " ++ show rel ++ " not smaller than 1e-12\n" ++
"expected: " ++ show d2 ++ "\n but got: " ++ show d1
isAlmostEqual a b =
failTest $ "Comparing different types: '" ++ show a ++ "' with '" ++
show b ++ "'"
serializeConf :: LispConfig -> String
serializeConf (LCList c) = "(" ++ unwords (map serializeConf c) ++ ")"
serializeConf (LCString s) = s
serializeConf (LCDouble d) = show d
serializeUptime :: UptimeInfo -> String
serializeUptime (UptimeInfo name idNum uptime) =
printf "%s\t%d\t%s" name idNum uptime
prop_config :: LispConfig -> Property
prop_config conf =
case A.parseOnly lispConfigParser . pack . serializeConf $ conf of
Left msg -> failTest $ "Parsing failed: " ++ msg
Right obtained -> counterexample "Failing almost equal check" $
isAlmostEqual obtained conf
prop_uptimeInfo :: UptimeInfo -> Property
prop_uptimeInfo uInfo =
case A.parseOnly uptimeLineParser . pack . serializeUptime $ uInfo of
Left msg -> failTest $ "Parsing failed: " ++ msg
Right obtained -> obtained ==? uInfo
case_xen401list :: Assertion
case_xen401list = testDomain "xen-xm-list-long-4.0.1.txt" $
Map.fromList
[ ("Domain-0", Domain 0 "Domain-0" 184000.41332 ActualRunning Nothing)
, ("instance1.example.com", Domain 119 "instance1.example.com" 24.116146647
ActualBlocked Nothing)
]
case_xen401uptime :: Assertion
case_xen401uptime = testUptimeInfo "xen-xm-uptime-4.0.1.txt" $
Map.fromList
[ (0, UptimeInfo "Domain-0" 0 "98 days, 2:27:44")
, (119, UptimeInfo "instance1.example.com" 119 "15 days, 20:57:07")
]
testSuite "Hypervisor/Xen/XmParser"
[ 'prop_config
, 'prop_uptimeInfo
, 'case_xen401list
, 'case_xen401uptime
]