Skip to content

Instantly share code, notes, and snippets.

instance
(Show a, Arbitrary a,
Testable testable)
=> Testable (a -> testable)
where
property f = forAll arbitrary f
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
module RapidCheck where
import Control.Monad
import Data.List
import System.Random
import Text.Show.Functions
gcd 1 1
> 1
gcd 0 0
> 0
rapidCheck prop_gcd_bad
> Failure {seed = 1034882204061803680,
counterExample = ["1","0"]}
type Shrinker a = a -> [a]
class Arbitrary a where
arbitrary :: Gen a
shrink :: Shrinker a
shrink = const []
forAll :: (Show a, Testable testable)
=> Gen a -> Shrink a -> (a -> testable) -> Property
forAll argGen shrink prop =
Property $ Gen $ \rand -> -- Create a new property that will
let (rand1, rand2) = split rand -- Split the generator in two
arg = runGen argGen rand1 -- Use the first generator to produce an arg
runSub = evalSubProp prop rand2 -- Factorize a runner for the sub-property
result = runSub arg -- Run the sub-property with value `arg`
in overFailure result $ \failure -> -- In case of failure,
shrinking shrink arg runSub -- Attempt to shrink the counter example
instance
(Show a, Arbitrary a, Testable testable)
=> Testable (a -> testable)
where
property = forAll arbitrary shrink
shrinking :: (Show a) => Shrink a -> a -> (a -> Result) -> Result
shrinking shrink arg runSub =
let children = shrink arg -- Get the children of the current branch
result = findFailing children runSub -- Look for the first failure
in case result of
Nothing -> Success
Just (shrunk, failure) -> -- In case a failure is found
shrinking shrink shrunk runSub -- Try to shrink further the child
<> -- OR (in case it fails)
addToCounterExample shrunk failure -- Add child to the counter example
instance Arbitrary Integer where
arbitrary = Gen $ \rand -> fromIntegral $ fst (next rand)
shrink n
| n == 0 = []
| otherwise = [abs n | n < 0] ++ 0 : rightDichotomy where
rightDichotomy =
takeWhile
(\m -> abs m < abs n)
[ n - i | i <- tail (iterate (`quot` 2) n)]
shrink 2048
> [0,1024,1536,1792,1920,1984,2016,2032,2040,2044,2046,2047]
shrink (-2048)
> [2048,0,-1024,-1536,-1792,-1920,-1984,-2016,-2032,-2040,-2044,-2046,-2047]