[Haskell-cafe] Quickcheck: Help on non trivial test

jean-christophe mincke jeanchristophe.mincke at gmail.com
Thu Jun 23 10:58:09 CEST 2011


Hello Café,

I am using quicheck for some kind of non trivial tests.

The general form of these tesst is summarized by the following code.


-- Function to be tested. Given a list of splitting functions, split the
given list
process :: [a] -> [[a] -> [a]] -> [a]
process l splitFuns =
    List.foldl proc l splitFuns
    where
    proc l splitFun = splitFun l

-- a split function generator
splitFunGen :: Gen ([a] -> [a])
splitFunGen = return $ proc
                      where
                      proc l = let splitPos = List.length l `div` 2 --
Problem I would like  splitPos = some random value between [0 and length of
l]
                                  in fst $ List.splitAt splitPos l

splitFunsGen :: Gen  [[a] -> [a]]
splitFunsGen = vectorOf 20 splitFunGen

instance Show a => Show ([a] -> [a]) where
    show _ = " a split fun "

r = quickCheck $ forAll splitFunsGen prop
    where
    prop splitFuns = let l = process [1..100] splitFuns
                            in List.length l >= 0 -- dummy test here for the
sake of example


The process to be tested takes a list that is randomly perturbated
(spitFuns). The result of each perturbation is fed into the next
perturbation.

Ideally I would like the perturbating function to depend on the previous
perturbated list (see computation of splitPos in splitFunGen).

I am not sure how I could use quickcheck in this case.

Has anyone a better idea?

Thanks

J-C
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110623/8f9dfe2c/attachment.htm>


More information about the Haskell-Cafe mailing list