{-# OPTIONS_GHC -O #-} import qualified Data.StorableVector as V import qualified Data.ByteString as P import QuickCheckUtils (V, W, X, P, mytest, eq1, eq2, eq3, eqnotnull1, eqnotnull2, eqnotnull3, ) import Text.Printf (printf) import System.Environment (getArgs) -- -- Data.StorableVector <=> ByteString -- prop_concatVP = (V.concat :: [V] -> V) `eq1` P.concat prop_nullVP = (V.null :: V -> Bool) `eq1` P.null prop_reverseVP = (V.reverse :: V -> V) `eq1` P.reverse prop_transposeVP = (V.transpose :: [V] -> [V]) `eq1` P.transpose prop_groupVP = (V.group :: V -> [V]) `eq1` P.group prop_initsVP = (V.inits :: V -> [V]) `eq1` P.inits prop_tailsVP = (V.tails :: V -> [V]) `eq1` P.tails prop_allVP = (V.all :: (W -> Bool) -> V -> Bool) `eq2` P.all prop_anyVP = (V.any :: (W -> Bool) -> V -> Bool) `eq2` P.any prop_appendVP = (V.append :: V -> V -> V) `eq2` P.append prop_breakVP = (V.break :: (W -> Bool) -> V -> (V, V)) `eq2` P.break prop_concatMapVP = (V.concatMap :: (W -> V) -> V -> V) `eq2` P.concatMap prop_consVP = (V.cons :: W -> V -> V) `eq2` P.cons prop_countVP = (V.count :: W -> V -> X) `eq2` P.count prop_dropVP = (V.drop :: X -> V -> V) `eq2` P.drop prop_dropWhileVP = (V.dropWhile :: (W -> Bool) -> V -> V) `eq2` P.dropWhile prop_filterVP = (V.filter :: (W -> Bool) -> V -> V) `eq2` P.filter prop_findVP = (V.find :: (W -> Bool) -> V -> Maybe W) `eq2` P.find prop_findIndexVP = (V.findIndex :: (W -> Bool) -> V -> Maybe X) `eq2` P.findIndex prop_findIndicesVP = (V.findIndices :: (W -> Bool) -> V -> [X]) `eq2` P.findIndices prop_isPrefixOfVP = (V.isPrefixOf :: V -> V -> Bool) `eq2` P.isPrefixOf prop_mapVP = (V.map :: (W -> W) -> V -> V) `eq2` P.map prop_replicateVP = (V.replicate :: X -> W -> V) `eq2` P.replicate prop_iterateVP = (V.iterateN :: X -> (W -> W) -> W -> V) `eq3` (\n f -> P.pack . take n . iterate f) prop_snocVP = (V.snoc :: V -> W -> V) `eq2` P.snoc prop_spanVP = (V.span :: (W -> Bool) -> V -> (V, V)) `eq2` P.span prop_splitVP = (V.split :: W -> V -> [V]) `eq2` P.split prop_splitAtVP = (V.splitAt :: X -> V -> (V, V)) `eq2` P.splitAt prop_takeVP = (V.take :: X -> V -> V) `eq2` P.take prop_takeWhileVP = (V.takeWhile :: (W -> Bool) -> V -> V) `eq2` P.takeWhile prop_elemVP = (V.elem :: W -> V -> Bool) `eq2` P.elem prop_notElemVP = (V.notElem :: W -> V -> Bool) `eq2` P.notElem prop_elemIndexVP = (V.elemIndex :: W -> V -> Maybe X) `eq2` P.elemIndex prop_elemIndicesVP = (V.elemIndices :: W -> V -> [X])`eq2` P.elemIndices prop_lengthVP = (V.length :: V -> X) `eq1` P.length prop_headVP = (V.head :: V -> W) `eqnotnull1` P.head prop_initVP = (V.init :: V -> V) `eqnotnull1` P.init prop_lastVP = (V.last :: V -> W) `eqnotnull1` P.last prop_maximumVP = (V.maximum :: V -> W) `eqnotnull1` P.maximum prop_minimumVP = (V.minimum :: V -> W) `eqnotnull1` P.minimum prop_tailVP = (V.tail :: V -> V) `eqnotnull1` P.tail prop_foldl1VP = (V.foldl1 :: (W -> W -> W) -> V -> W) `eqnotnull2` P.foldl1 prop_foldl1VP' = (V.foldl1' :: (W -> W -> W) -> V -> W) `eqnotnull2` P.foldl1' prop_foldr1VP = (V.foldr1 :: (W -> W -> W) -> V -> W) `eqnotnull2` P.foldr1 prop_scanlVP = (V.scanl :: (W -> W -> W) -> W -> V -> V) `eqnotnull3` P.scanl prop_scanrVP = (V.scanr :: (W -> W -> W) -> W -> V -> V) `eqnotnull3` P.scanr prop_eqVP = eq2 ((==) :: V -> V -> Bool) ((==) :: P -> P -> Bool) prop_foldlVP = eq3 (V.foldl :: (X -> W -> X) -> X -> V -> X) (P.foldl :: (X -> W -> X) -> X -> P -> X) prop_foldlVP' = eq3 (V.foldl' :: (X -> W -> X) -> X -> V -> X) (P.foldl' :: (X -> W -> X) -> X -> P -> X) prop_foldrVP = eq3 (V.foldr :: (W -> X -> X) -> X -> V -> X) (P.foldr :: (W -> X -> X) -> X -> P -> X) prop_mapAccumLVP = eq3 (V.mapAccumL :: (X -> W -> (X,W)) -> X -> V -> (X, V)) (P.mapAccumL :: (X -> W -> (X,W)) -> X -> P -> (X, P)) prop_mapAccumRVP = eq3 (V.mapAccumR :: (X -> W -> (X,W)) -> X -> V -> (X, V)) (P.mapAccumR :: (X -> W -> (X,W)) -> X -> P -> (X, P)) prop_zipWithVP = eq3 (V.zipWith :: (W -> W -> W) -> V -> V -> V) -- (P.zipWith :: (W -> W -> W) -> P -> P -> P) (\f x y -> P.pack (P.zipWith f x y) :: P) prop_unfoldrVP = eq3 ((\n f a -> V.take (fromIntegral n) $ V.unfoldr f a) :: Int -> (X -> Maybe (W,X)) -> X -> V) ((\n f a -> fst $ P.unfoldrN n f a) :: Int -> (X -> Maybe (W,X)) -> X -> P) ------------------------------------------------------------------------ -- StorableVector <=> ByteString vp_tests = [("all", mytest prop_allVP) ,("any", mytest prop_anyVP) ,("append", mytest prop_appendVP) ,("concat", mytest prop_concatVP) ,("cons", mytest prop_consVP) ,("eq", mytest prop_eqVP) ,("filter", mytest prop_filterVP) ,("find", mytest prop_findVP) ,("findIndex", mytest prop_findIndexVP) ,("findIndices", mytest prop_findIndicesVP) ,("foldl", mytest prop_foldlVP) ,("foldl'", mytest prop_foldlVP') ,("foldl1", mytest prop_foldl1VP) ,("foldl1'", mytest prop_foldl1VP') ,("foldr", mytest prop_foldrVP) ,("foldr1", mytest prop_foldr1VP) ,("mapAccumL", mytest prop_mapAccumLVP) ,("mapAccumR", mytest prop_mapAccumRVP) ,("zipWith", mytest prop_zipWithVP) -- ,("unfoldr", mytest prop_unfoldrVP) ,("head", mytest prop_headVP) ,("init", mytest prop_initVP) ,("isPrefixOf", mytest prop_isPrefixOfVP) ,("last", mytest prop_lastVP) ,("length", mytest prop_lengthVP) ,("map", mytest prop_mapVP) ,("maximum ", mytest prop_maximumVP) ,("minimum" , mytest prop_minimumVP) ,("null", mytest prop_nullVP) ,("reverse", mytest prop_reverseVP) ,("snoc", mytest prop_snocVP) ,("tail", mytest prop_tailVP) ,("scanl", mytest prop_scanlVP) ,("scanr", mytest prop_scanrVP) ,("transpose", mytest prop_transposeVP) ,("replicate", mytest prop_replicateVP) ,("iterateN", mytest prop_iterateVP) ,("take", mytest prop_takeVP) ,("drop", mytest prop_dropVP) ,("splitAt", mytest prop_splitAtVP) ,("takeWhile", mytest prop_takeWhileVP) ,("dropWhile", mytest prop_dropWhileVP) ,("break", mytest prop_breakVP) ,("span", mytest prop_spanVP) ,("split", mytest prop_splitVP) ,("count", mytest prop_countVP) ,("group", mytest prop_groupVP) ,("inits", mytest prop_initsVP) ,("tails", mytest prop_tailsVP) ,("elem", mytest prop_elemVP) ,("notElem", mytest prop_notElemVP) ,("elemIndex", mytest prop_elemIndexVP) ,("elemIndices", mytest prop_elemIndicesVP) ,("concatMap", mytest prop_concatMapVP) ] ------------------------------------------------------------------------ -- The entry point main = run vp_tests run :: [(String, Int -> IO ())] -> IO () run tests = do x <- getArgs let n = if null x then 100 else read . head $ x mapM_ (\(s,a) -> printf "%-25s: " s >> a n) tests