import Test.QuickCheck import Data.AttoBencode import Control.Monad (liftM) import Data.Map (Map, fromList) import Test.Framework (Test, defaultMain) import Test.Framework.Providers.QuickCheck2 (testProperty) import qualified Data.ByteString.Char8 as B instance Arbitrary BValue where arbitrary = sized f -- need to mess with size to prevent generation of infinite test cases -- for recursive constructors where f 0 = oneof [liftM BString arbitrary ,liftM BInt arbitrary] f n = oneof [liftM BString arbitrary ,liftM BInt arbitrary ,liftM BList $ listOf $ f $ n `div` 5 ,liftM BDict $ dict $ n `div` 5] dict :: Int -> Gen Dict dict n = liftM fromList (listOf (pair n)) pair :: Int -> Gen (B.ByteString, BValue) pair n = do bs <- arbitrary bv <- f n return (bs, bv) instance Arbitrary B.ByteString where arbitrary = fmap B.pack arbitrary instance FromBencode BValue where fromBencode = Just prop_EncodeInteger :: Integer -> Bool prop_EncodeInteger n = encode (BInt n) == B.pack ("i" ++ show n ++ "e") prop_EncodeString :: B.ByteString -> Bool prop_EncodeString bs = encode (BString bs) == B.pack (show (B.length bs) ++ ":") `B.append` bs prop_EncodeDecode :: BValue -> Bool prop_EncodeDecode bv = case decode (encode bv) of Just bv' -> bv == bv' Nothing -> False main :: IO () main = defaultMain tests tests :: [Test] tests = [testProperty "prop_EncodeInteger" prop_EncodeInteger ,testProperty "prop_EncodeString" prop_EncodeString ,testProperty "prop_EncodeDecode" prop_EncodeDecode]