{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE CPP #-}
#ifndef NO_TYPEABLE
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
#endif
#ifndef NO_SAFE_HASKELL
{-# LANGUAGE Safe #-}
#endif
module Test.QuickCheck.Property where
import Test.QuickCheck.Gen
import Test.QuickCheck.Gen.Unsafe
import Test.QuickCheck.Arbitrary
import Test.QuickCheck.Text( isOneLine, putLine )
import Test.QuickCheck.Exception
import Test.QuickCheck.State( State(terminal), Confidence(..) )
#ifndef NO_TIMEOUT
import System.Timeout(timeout)
#endif
import Data.Maybe
import Control.Applicative
import Control.Monad
import qualified Data.Map as Map
import Data.Map(Map)
import qualified Data.Set as Set
import Data.Set(Set)
#ifndef NO_DEEPSEQ
import Control.DeepSeq
#endif
#ifndef NO_TYPEABLE
import Data.Typeable (Typeable, cast)
#endif
import Data.Maybe
infixr 0 ==>
infixr 1 .&.
infixr 1 .&&.
infixr 1 .||.
newtype Property = MkProperty { Property -> Gen Prop
unProperty :: Gen Prop }
#ifndef NO_TYPEABLE
deriving (Typeable)
#endif
class Testable prop where
property :: prop -> Property
propertyForAllShrinkShow :: Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
propertyForAllShrinkShow Gen a
gen a -> [a]
shr a -> [String]
shw a -> prop
f =
Gen a -> (a -> [a]) -> (a -> Property) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrinkBlind Gen a
gen a -> [a]
shr ((a -> Property) -> Property) -> (a -> Property) -> Property
forall a b. (a -> b) -> a -> b
$
\a
x -> (String -> Property -> Property)
-> Property -> [String] -> Property
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr String -> Property -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (prop -> Property
forall prop. Testable prop => prop -> Property
property (a -> prop
f a
x)) (a -> [String]
shw a
x)
data Discard = Discard
instance Testable Discard where
property :: Discard -> Property
property Discard
_ = Result -> Property
forall prop. Testable prop => prop -> Property
property Result
rejected
instance Testable () where
property :: () -> Property
property = Result -> Property
forall prop. Testable prop => prop -> Property
property (Result -> Property) -> (() -> Result) -> () -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. () -> Result
liftUnit
where
liftUnit :: () -> Result
liftUnit () = Result
succeeded
instance Testable prop => Testable (Maybe prop) where
property :: Maybe prop -> Property
property = Property -> Property
forall prop. Testable prop => prop -> Property
property (Property -> Property)
-> (Maybe prop -> Property) -> Maybe prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe prop -> Property
forall prop. Testable prop => Maybe prop -> Property
liftMaybe
where
liftMaybe :: Maybe prop -> Property
liftMaybe Maybe prop
Nothing = Discard -> Property
forall prop. Testable prop => prop -> Property
property Discard
Discard
liftMaybe (Just prop
prop) = prop -> Property
forall prop. Testable prop => prop -> Property
property prop
prop
instance Testable Bool where
property :: Bool -> Property
property = Result -> Property
forall prop. Testable prop => prop -> Property
property (Result -> Property) -> (Bool -> Result) -> Bool -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Result
liftBool
instance Testable Result where
property :: Result -> Property
property = Gen Prop -> Property
MkProperty (Gen Prop -> Property)
-> (Result -> Gen Prop) -> Result -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Prop -> Gen Prop
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (Prop -> Gen Prop) -> (Result -> Prop) -> Result -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rose Result -> Prop
MkProp (Rose Result -> Prop) -> (Result -> Rose Result) -> Result -> Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rose Result -> Rose Result
protectResults (Rose Result -> Rose Result)
-> (Result -> Rose Result) -> Result -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return
instance Testable Prop where
property :: Prop -> Property
property Prop
p = Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> (Prop -> Gen Prop) -> Prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Prop -> Gen Prop
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (Prop -> Gen Prop) -> (Prop -> Prop) -> Prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Prop -> Prop
protectProp (Prop -> Property) -> Prop -> Property
forall a b. (a -> b) -> a -> b
$ Prop
p
instance Testable prop => Testable (Gen prop) where
property :: Gen prop -> Property
property Gen prop
mp = Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> Gen Prop -> Property
forall a b. (a -> b) -> a -> b
$ do prop
p <- Gen prop
mp; Property -> Gen Prop
unProperty (prop -> Property
forall prop. Testable prop => prop -> Property
property prop
p)
instance Testable Property where
property :: Property -> Property
property (MkProperty Gen Prop
mp) = Gen Prop -> Property
MkProperty ((Prop -> Prop) -> Gen Prop -> Gen Prop
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Prop
protectProp Gen Prop
mp)
{-# DEPRECATED morallyDubiousIOProperty "Use 'ioProperty' instead" #-}
morallyDubiousIOProperty :: Testable prop => IO prop -> Property
morallyDubiousIOProperty :: forall prop. Testable prop => IO prop -> Property
morallyDubiousIOProperty = IO prop -> Property
forall prop. Testable prop => IO prop -> Property
ioProperty
ioProperty :: Testable prop => IO prop -> Property
ioProperty :: forall prop. Testable prop => IO prop -> Property
ioProperty IO prop
prop = IO Property -> Property
forall prop. Testable prop => IO prop -> Property
idempotentIOProperty ((prop -> Property) -> IO prop -> IO Property
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap prop -> Property
forall prop. Testable prop => prop -> Property
noShrinking IO prop
prop)
idempotentIOProperty :: Testable prop => IO prop -> Property
idempotentIOProperty :: forall prop. Testable prop => IO prop -> Property
idempotentIOProperty =
Gen Prop -> Property
MkProperty (Gen Prop -> Property)
-> (IO prop -> Gen Prop) -> IO prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IO Prop -> Prop) -> Gen (IO Prop) -> Gen Prop
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rose Result -> Prop
MkProp (Rose Result -> Prop)
-> (IO Prop -> Rose Result) -> IO Prop -> Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Rose Result) -> Rose Result
ioRose (IO (Rose Result) -> Rose Result)
-> (IO Prop -> IO (Rose Result)) -> IO Prop -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Prop -> Rose Result) -> IO Prop -> IO (Rose Result)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Rose Result
unProp) (Gen (IO Prop) -> Gen Prop)
-> (IO prop -> Gen (IO Prop)) -> IO prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
IO (Gen Prop) -> Gen (IO Prop)
forall (m :: * -> *) a. Monad m => m (Gen a) -> Gen (m a)
promote (IO (Gen Prop) -> Gen (IO Prop))
-> (IO prop -> IO (Gen Prop)) -> IO prop -> Gen (IO Prop)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (prop -> Gen Prop) -> IO prop -> IO (Gen Prop)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Property -> Gen Prop
unProperty (Property -> Gen Prop) -> (prop -> Property) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. prop -> Property
forall prop. Testable prop => prop -> Property
property)
instance (Arbitrary a, Show a, Testable prop) => Testable (a -> prop) where
property :: (a -> prop) -> Property
property a -> prop
f =
Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
forall a.
Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
propertyForAllShrinkShow Gen a
forall a. Arbitrary a => Gen a
arbitrary a -> [a]
forall a. Arbitrary a => a -> [a]
shrink (String -> [String]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> [String]) -> (a -> String) -> a -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show) a -> prop
f
propertyForAllShrinkShow :: forall a.
Gen a
-> (a -> [a]) -> (a -> [String]) -> (a -> a -> prop) -> Property
propertyForAllShrinkShow Gen a
gen a -> [a]
shr a -> [String]
shw a -> a -> prop
f =
Gen (a, a)
-> ((a, a) -> [(a, a)])
-> ((a, a) -> [String])
-> ((a, a) -> prop)
-> Property
forall a.
Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> prop) -> Property
propertyForAllShrinkShow
((a -> a -> (a, a)) -> Gen a -> Gen a -> Gen (a, a)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) Gen a
gen Gen a
forall a. Arbitrary a => Gen a
arbitrary)
((a -> [a]) -> (a -> [a]) -> (a, a) -> [(a, a)]
forall a b. (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)]
forall (f :: * -> * -> *) a b.
Arbitrary2 f =>
(a -> [a]) -> (b -> [b]) -> f a b -> [f a b]
liftShrink2 a -> [a]
shr a -> [a]
forall a. Arbitrary a => a -> [a]
shrink)
(\(a
x, a
y) -> a -> [String]
shw a
x [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [a -> String
forall a. Show a => a -> String
show a
y])
((a -> a -> prop) -> (a, a) -> prop
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> prop
f)
protect :: (AnException -> a) -> IO a -> IO a
protect :: forall a. (AnException -> a) -> IO a -> IO a
protect AnException -> a
f IO a
x = (AnException -> a) -> (a -> a) -> Either AnException a -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either AnException -> a
f a -> a
forall a. a -> a
id (Either AnException a -> a) -> IO (Either AnException a) -> IO a
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` IO a -> IO (Either AnException a)
forall a. IO a -> IO (Either AnException a)
tryEvaluateIO IO a
x
newtype Prop = MkProp{ Prop -> Rose Result
unProp :: Rose Result }
data Rose a = MkRose a [Rose a] | IORose (IO (Rose a))
ioRose :: IO (Rose Result) -> Rose Result
ioRose :: IO (Rose Result) -> Rose Result
ioRose = IO (Rose Result) -> Rose Result
forall a. IO (Rose a) -> Rose a
IORose (IO (Rose Result) -> Rose Result)
-> (IO (Rose Result) -> IO (Rose Result))
-> IO (Rose Result)
-> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Rose Result) -> IO (Rose Result)
protectRose
joinRose :: Rose (Rose a) -> Rose a
joinRose :: forall a. Rose (Rose a) -> Rose a
joinRose (IORose IO (Rose (Rose a))
rs) = IO (Rose a) -> Rose a
forall a. IO (Rose a) -> Rose a
IORose ((Rose (Rose a) -> Rose a) -> IO (Rose (Rose a)) -> IO (Rose a)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Rose (Rose a) -> Rose a
forall a. Rose (Rose a) -> Rose a
joinRose IO (Rose (Rose a))
rs)
joinRose (MkRose (IORose IO (Rose a)
rm) [Rose (Rose a)]
rs) = IO (Rose a) -> Rose a
forall a. IO (Rose a) -> Rose a
IORose (IO (Rose a) -> Rose a) -> IO (Rose a) -> Rose a
forall a b. (a -> b) -> a -> b
$ do Rose a
r <- IO (Rose a)
rm; Rose a -> IO (Rose a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rose (Rose a) -> Rose a
forall a. Rose (Rose a) -> Rose a
joinRose (Rose a -> [Rose (Rose a)] -> Rose (Rose a)
forall a. a -> [Rose a] -> Rose a
MkRose Rose a
r [Rose (Rose a)]
rs))
joinRose (MkRose (MkRose a
x [Rose a]
ts) [Rose (Rose a)]
tts) =
a -> [Rose a] -> Rose a
forall a. a -> [Rose a] -> Rose a
MkRose a
x ((Rose (Rose a) -> Rose a) -> [Rose (Rose a)] -> [Rose a]
forall a b. (a -> b) -> [a] -> [b]
map Rose (Rose a) -> Rose a
forall a. Rose (Rose a) -> Rose a
joinRose [Rose (Rose a)]
tts [Rose a] -> [Rose a] -> [Rose a]
forall a. [a] -> [a] -> [a]
++ [Rose a]
ts)
instance Functor Rose where
fmap :: forall a b. (a -> b) -> Rose a -> Rose b
fmap a -> b
f (IORose IO (Rose a)
rs) = IO (Rose b) -> Rose b
forall a. IO (Rose a) -> Rose a
IORose ((Rose a -> Rose b) -> IO (Rose a) -> IO (Rose b)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Rose a -> Rose b
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) IO (Rose a)
rs)
fmap a -> b
f (MkRose a
x [Rose a]
rs) = b -> [Rose b] -> Rose b
forall a. a -> [Rose a] -> Rose a
MkRose (a -> b
f a
x) [ (a -> b) -> Rose a -> Rose b
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Rose a
r | Rose a
r <- [Rose a]
rs ]
instance Applicative Rose where
pure :: forall a. a -> Rose a
pure a
x = a -> [Rose a] -> Rose a
forall a. a -> [Rose a] -> Rose a
MkRose a
x []
<*> :: forall a b. Rose (a -> b) -> Rose a -> Rose b
(<*>) = ((a -> b) -> a -> b) -> Rose (a -> b) -> Rose a -> Rose b
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
($)
instance Monad Rose where
return :: forall a. a -> Rose a
return = a -> Rose a
forall a. a -> Rose a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Rose a
m >>= :: forall a b. Rose a -> (a -> Rose b) -> Rose b
>>= a -> Rose b
k = Rose (Rose b) -> Rose b
forall a. Rose (Rose a) -> Rose a
joinRose ((a -> Rose b) -> Rose a -> Rose (Rose b)
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Rose b
k Rose a
m)
reduceRose :: Rose Result -> IO (Rose Result)
reduceRose :: Rose Result -> IO (Rose Result)
reduceRose r :: Rose Result
r@(MkRose Result
_ [Rose Result]
_) = Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rose Result
r
reduceRose (IORose IO (Rose Result)
m) = IO (Rose Result)
m IO (Rose Result)
-> (Rose Result -> IO (Rose Result)) -> IO (Rose Result)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Rose Result -> IO (Rose Result)
reduceRose
onRose :: (a -> [Rose a] -> Rose a) -> Rose a -> Rose a
onRose :: forall a. (a -> [Rose a] -> Rose a) -> Rose a -> Rose a
onRose a -> [Rose a] -> Rose a
f (MkRose a
x [Rose a]
rs) = a -> [Rose a] -> Rose a
f a
x [Rose a]
rs
onRose a -> [Rose a] -> Rose a
f (IORose IO (Rose a)
m) = IO (Rose a) -> Rose a
forall a. IO (Rose a) -> Rose a
IORose ((Rose a -> Rose a) -> IO (Rose a) -> IO (Rose a)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> [Rose a] -> Rose a) -> Rose a -> Rose a
forall a. (a -> [Rose a] -> Rose a) -> Rose a -> Rose a
onRose a -> [Rose a] -> Rose a
f) IO (Rose a)
m)
protectRose :: IO (Rose Result) -> IO (Rose Result)
protectRose :: IO (Rose Result) -> IO (Rose Result)
protectRose = (AnException -> Rose Result)
-> IO (Rose Result) -> IO (Rose Result)
forall a. (AnException -> a) -> IO a -> IO a
protect (Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> Rose Result)
-> (AnException -> Result) -> AnException -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> AnException -> Result
exception String
"Exception")
protectProp :: Prop -> Prop
protectProp :: Prop -> Prop
protectProp (MkProp Rose Result
r) = Rose Result -> Prop
MkProp (IO (Rose Result) -> Rose Result
forall a. IO (Rose a) -> Rose a
IORose (IO (Rose Result) -> Rose Result)
-> (Rose Result -> IO (Rose Result)) -> Rose Result -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Rose Result) -> IO (Rose Result)
protectRose (IO (Rose Result) -> IO (Rose Result))
-> (Rose Result -> IO (Rose Result))
-> Rose Result
-> IO (Rose Result)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rose Result -> Rose Result) -> Rose Result -> Rose Result
forall a b. (a -> b) -> a -> b
$ Rose Result
r)
protectResults :: Rose Result -> Rose Result
protectResults :: Rose Result -> Rose Result
protectResults = (Result -> [Rose Result] -> Rose Result)
-> Rose Result -> Rose Result
forall a. (a -> [Rose a] -> Rose a) -> Rose a -> Rose a
onRose ((Result -> [Rose Result] -> Rose Result)
-> Rose Result -> Rose Result)
-> (Result -> [Rose Result] -> Rose Result)
-> Rose Result
-> Rose Result
forall a b. (a -> b) -> a -> b
$ \Result
x [Rose Result]
rs ->
IO (Rose Result) -> Rose Result
forall a. IO (Rose a) -> Rose a
IORose (IO (Rose Result) -> Rose Result)
-> IO (Rose Result) -> Rose Result
forall a b. (a -> b) -> a -> b
$ do
Result
y <- IO Result -> IO Result
protectResult (Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
x)
Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose Result
y ((Rose Result -> Rose Result) -> [Rose Result] -> [Rose Result]
forall a b. (a -> b) -> [a] -> [b]
map Rose Result -> Rose Result
protectResults [Rose Result]
rs))
data Callback
= PostTest CallbackKind (State -> Result -> IO ())
| PostFinalFailure CallbackKind (State -> Result -> IO ())
data CallbackKind = Counterexample
| NotCounterexample
#ifndef NO_TYPEABLE
data Witness = forall a. (Typeable a, Show a) => Wit a
instance Show Witness where
show :: Witness -> String
show (Wit a
a) = a -> String
forall a. Show a => a -> String
show a
a
coerceWitness :: Typeable a => Witness -> a
coerceWitness :: forall a. Typeable a => Witness -> a
coerceWitness (Wit a
a) = case a -> Maybe a
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
a of
Maybe a
Nothing -> String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Can't coerceWitness " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
a
Just a
a -> a
a
castWitness :: Typeable a => Witness -> Maybe a
castWitness :: forall a. Typeable a => Witness -> Maybe a
castWitness (Wit a
a) = a -> Maybe a
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
a
#define WITNESSES(a) , theWitnesses a
#else
#define WITNESSES(a)
#endif
data Result
= MkResult
{ Result -> Maybe Bool
ok :: Maybe Bool
, Result -> Bool
expect :: Bool
, Result -> String
reason :: String
, Result -> Maybe AnException
theException :: Maybe AnException
, Result -> Bool
abort :: Bool
, Result -> Maybe Int
maybeNumTests :: Maybe Int
, Result -> Maybe Confidence
maybeCheckCoverage :: Maybe Confidence
, Result -> Maybe Int
maybeDiscardedRatio :: Maybe Int
, Result -> Maybe Int
maybeMaxShrinks :: Maybe Int
, Result -> Maybe Int
maybeMaxTestSize :: Maybe Int
, Result -> [String]
labels :: [String]
, Result -> [(String, Bool)]
classes :: [(String, Bool)]
, Result -> [(String, String)]
tables :: [(String, String)]
, Result -> [(Maybe String, String, Double)]
requiredCoverage :: [(Maybe String, String, Double)]
, Result -> [Callback]
callbacks :: [Callback]
, Result -> [String]
testCase :: [String]
WITNESSES(:: [Witness])
}
exception :: String -> AnException -> Result
exception :: String -> AnException -> Result
exception String
msg AnException
err
| AnException -> Bool
isDiscard AnException
err = Result
rejected
| Bool
otherwise = Result
failed{ reason = formatException msg err,
theException = Just err }
formatException :: String -> AnException -> String
formatException :: String -> AnException -> String
formatException String
msg AnException
err = String
msg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
format (AnException -> String
forall a. Show a => a -> String
show AnException
err)
where format :: ShowS
format String
xs | String -> Bool
isOneLine String
xs = String
" '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
xs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
| Bool
otherwise = String
"\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unlines [ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
l | String
l <- String -> [String]
lines String
xs ]
protectResult :: IO Result -> IO Result
protectResult :: IO Result -> IO Result
protectResult = (AnException -> Result) -> IO Result -> IO Result
forall a. (AnException -> a) -> IO a -> IO a
protect (String -> AnException -> Result
exception String
"Exception")
succeeded, failed, rejected :: Result
(Result
succeeded, Result
failed, Result
rejected) =
(Result
result{ ok = Just True },
Result
result{ ok = Just False },
Result
result{ ok = Nothing })
where
result :: Result
result =
MkResult
{ ok :: Maybe Bool
ok = Maybe Bool
forall a. HasCallStack => a
undefined
, expect :: Bool
expect = Bool
True
, reason :: String
reason = String
""
, theException :: Maybe AnException
theException = Maybe AnException
forall a. Maybe a
Nothing
, abort :: Bool
abort = Bool
False
, maybeNumTests :: Maybe Int
maybeNumTests = Maybe Int
forall a. Maybe a
Nothing
, maybeCheckCoverage :: Maybe Confidence
maybeCheckCoverage = Maybe Confidence
forall a. Maybe a
Nothing
, maybeDiscardedRatio :: Maybe Int
maybeDiscardedRatio = Maybe Int
forall a. Maybe a
Nothing
, maybeMaxShrinks :: Maybe Int
maybeMaxShrinks = Maybe Int
forall a. Maybe a
Nothing
, maybeMaxTestSize :: Maybe Int
maybeMaxTestSize = Maybe Int
forall a. Maybe a
Nothing
, labels :: [String]
labels = []
, classes :: [(String, Bool)]
classes = []
, tables :: [(String, String)]
tables = []
, requiredCoverage :: [(Maybe String, String, Double)]
requiredCoverage = []
, callbacks :: [Callback]
callbacks = []
, testCase :: [String]
testCase = []
WITNESSES(= [])
}
liftBool :: Bool -> Result
liftBool :: Bool -> Result
liftBool Bool
True = Result
succeeded
liftBool Bool
False = Result
failed { reason = "Falsified" }
mapResult :: Testable prop => (Result -> Result) -> prop -> Property
mapResult :: forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapResult Result -> Result
f = (Rose Result -> Rose Result) -> prop -> Property
forall prop.
Testable prop =>
(Rose Result -> Rose Result) -> prop -> Property
mapRoseResult (Rose Result -> Rose Result
protectResults (Rose Result -> Rose Result)
-> (Rose Result -> Rose Result) -> Rose Result -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Result -> Result) -> Rose Result -> Rose Result
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Result -> Result
f)
mapTotalResult :: Testable prop => (Result -> Result) -> prop -> Property
mapTotalResult :: forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult Result -> Result
f = (Rose Result -> Rose Result) -> prop -> Property
forall prop.
Testable prop =>
(Rose Result -> Rose Result) -> prop -> Property
mapRoseResult ((Result -> Result) -> Rose Result -> Rose Result
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Result -> Result
f)
mapRoseResult :: Testable prop => (Rose Result -> Rose Result) -> prop -> Property
mapRoseResult :: forall prop.
Testable prop =>
(Rose Result -> Rose Result) -> prop -> Property
mapRoseResult Rose Result -> Rose Result
f = (Prop -> Prop) -> prop -> Property
forall prop. Testable prop => (Prop -> Prop) -> prop -> Property
mapProp (\(MkProp Rose Result
t) -> Rose Result -> Prop
MkProp (Rose Result -> Rose Result
f Rose Result
t))
mapProp :: Testable prop => (Prop -> Prop) -> prop -> Property
mapProp :: forall prop. Testable prop => (Prop -> Prop) -> prop -> Property
mapProp Prop -> Prop
f = Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> (prop -> Gen Prop) -> prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Prop -> Prop) -> Gen Prop -> Gen Prop
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Prop
f (Gen Prop -> Gen Prop) -> (prop -> Gen Prop) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Property -> Gen Prop
unProperty (Property -> Gen Prop) -> (prop -> Property) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. prop -> Property
forall prop. Testable prop => prop -> Property
property
mapSize :: Testable prop => (Int -> Int) -> prop -> Property
mapSize :: forall prop. Testable prop => (Int -> Int) -> prop -> Property
mapSize Int -> Int
f = Gen Prop -> Property
forall prop. Testable prop => prop -> Property
property (Gen Prop -> Property) -> (prop -> Gen Prop) -> prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> Gen Prop -> Gen Prop
forall a. (Int -> Int) -> Gen a -> Gen a
scale Int -> Int
f (Gen Prop -> Gen Prop) -> (prop -> Gen Prop) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Property -> Gen Prop
unProperty (Property -> Gen Prop) -> (prop -> Property) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. prop -> Property
forall prop. Testable prop => prop -> Property
property
shrinking :: Testable prop =>
(a -> [a])
-> a
-> (a -> prop) -> Property
shrinking :: forall prop a.
Testable prop =>
(a -> [a]) -> a -> (a -> prop) -> Property
shrinking a -> [a]
shrinker a
x0 a -> prop
pf = Gen Prop -> Property
MkProperty ((Rose Prop -> Prop) -> Gen (Rose Prop) -> Gen Prop
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rose Result -> Prop
MkProp (Rose Result -> Prop)
-> (Rose Prop -> Rose Result) -> Rose Prop -> Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rose (Rose Result) -> Rose Result
forall a. Rose (Rose a) -> Rose a
joinRose (Rose (Rose Result) -> Rose Result)
-> (Rose Prop -> Rose (Rose Result)) -> Rose Prop -> Rose Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Prop -> Rose Result) -> Rose Prop -> Rose (Rose Result)
forall a b. (a -> b) -> Rose a -> Rose b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Rose Result
unProp) (Rose (Gen Prop) -> Gen (Rose Prop)
forall (m :: * -> *) a. Monad m => m (Gen a) -> Gen (m a)
promote (a -> Rose (Gen Prop)
props a
x0)))
where
props :: a -> Rose (Gen Prop)
props a
x =
Gen Prop -> [Rose (Gen Prop)] -> Rose (Gen Prop)
forall a. a -> [Rose a] -> Rose a
MkRose (Property -> Gen Prop
unProperty (prop -> Property
forall prop. Testable prop => prop -> Property
property (a -> prop
pf a
x))) [ a -> Rose (Gen Prop)
props a
x' | a
x' <- a -> [a]
shrinker a
x ]
noShrinking :: Testable prop => prop -> Property
noShrinking :: forall prop. Testable prop => prop -> Property
noShrinking = (Rose Result -> Rose Result) -> prop -> Property
forall prop.
Testable prop =>
(Rose Result -> Rose Result) -> prop -> Property
mapRoseResult ((Result -> [Rose Result] -> Rose Result)
-> Rose Result -> Rose Result
forall a. (a -> [Rose a] -> Rose a) -> Rose a -> Rose a
onRose (\Result
res [Rose Result]
_ -> Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose Result
res []))
callback :: Testable prop => Callback -> prop -> Property
callback :: forall prop. Testable prop => Callback -> prop -> Property
callback Callback
cb = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ callbacks = cb : callbacks res })
counterexample :: Testable prop => String -> prop -> Property
counterexample :: forall prop. Testable prop => String -> prop -> Property
counterexample String
s =
(Result -> Result) -> Property -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ testCase = s:testCase res }) (Property -> Property) -> (prop -> Property) -> prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Callback -> prop -> Property
forall prop. Testable prop => Callback -> prop -> Property
callback (CallbackKind -> (State -> Result -> IO ()) -> Callback
PostFinalFailure CallbackKind
Counterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
st Result
_res -> do
String
s <- String -> IO String
showCounterexample String
s
Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) String
s)
showCounterexample :: String -> IO String
showCounterexample :: String -> IO String
showCounterexample String
s = do
let force :: [a] -> m ()
force [] = () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
force (a
x:[a]
xs) = a
x a -> m () -> m ()
forall a b. a -> b -> b
`seq` [a] -> m ()
force [a]
xs
Either AnException ()
res <- IO () -> IO (Either AnException ())
forall a. IO a -> IO (Either AnException a)
tryEvaluateIO (String -> IO ()
forall {m :: * -> *} {a}. Monad m => [a] -> m ()
force String
s)
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$
case Either AnException ()
res of
Left AnException
err ->
String -> AnException -> String
formatException String
"Exception thrown while showing test case" AnException
err
Right () ->
String
s
{-# DEPRECATED printTestCase "Use counterexample instead" #-}
printTestCase :: Testable prop => String -> prop -> Property
printTestCase :: forall prop. Testable prop => String -> prop -> Property
printTestCase = String -> prop -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample
whenFail :: Testable prop => IO () -> prop -> Property
whenFail :: forall prop. Testable prop => IO () -> prop -> Property
whenFail IO ()
m =
Callback -> prop -> Property
forall prop. Testable prop => Callback -> prop -> Property
callback (Callback -> prop -> Property) -> Callback -> prop -> Property
forall a b. (a -> b) -> a -> b
$ CallbackKind -> (State -> Result -> IO ()) -> Callback
PostFinalFailure CallbackKind
NotCounterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
_st Result
_res ->
IO ()
m
whenFail' :: Testable prop => IO () -> prop -> Property
whenFail' :: forall prop. Testable prop => IO () -> prop -> Property
whenFail' IO ()
m =
Callback -> prop -> Property
forall prop. Testable prop => Callback -> prop -> Property
callback (Callback -> prop -> Property) -> Callback -> prop -> Property
forall a b. (a -> b) -> a -> b
$ CallbackKind -> (State -> Result -> IO ()) -> Callback
PostTest CallbackKind
NotCounterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
_st Result
res ->
if Result -> Maybe Bool
ok Result
res Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
then IO ()
m
else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
verbose :: Testable prop => prop -> Property
verbose :: forall prop. Testable prop => prop -> Property
verbose = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapResult (\Result
res -> Result
res { callbacks = newCallback (callbacks res):callbacks res })
where newCallback :: [Callback] -> Callback
newCallback [Callback]
cbs =
CallbackKind -> (State -> Result -> IO ()) -> Callback
PostTest CallbackKind
Counterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
st Result
res -> do
Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) (Result -> String
status Result
res String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":")
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ State -> Result -> IO ()
f State
st Result
res | PostFinalFailure CallbackKind
Counterexample State -> Result -> IO ()
f <- [Callback]
cbs ]
Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) String
""
status :: Result -> String
status MkResult{ok :: Result -> Maybe Bool
ok = Just Bool
True} = String
"Passed"
status MkResult{ok :: Result -> Maybe Bool
ok = Just Bool
False} = String
"Failed"
status MkResult{ok :: Result -> Maybe Bool
ok = Maybe Bool
Nothing} = String
"Skipped (precondition false)"
verboseShrinking :: Testable prop => prop -> Property
verboseShrinking :: forall prop. Testable prop => prop -> Property
verboseShrinking = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapResult (\Result
res -> Result
res { callbacks = newCallback (callbacks res):callbacks res })
where newCallback :: [Callback] -> Callback
newCallback [Callback]
cbs =
CallbackKind -> (State -> Result -> IO ()) -> Callback
PostTest CallbackKind
Counterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
st Result
res ->
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result -> Maybe Bool
ok Result
res Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) String
"Failed:"
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ State -> Result -> IO ()
f State
st Result
res | PostFinalFailure CallbackKind
Counterexample State -> Result -> IO ()
f <- [Callback]
cbs ]
Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) String
""
expectFailure :: Testable prop => prop -> Property
expectFailure :: forall prop. Testable prop => prop -> Property
expectFailure = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ expect = False })
once :: Testable prop => prop -> Property
once :: forall prop. Testable prop => prop -> Property
once = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ abort = True })
again :: Testable prop => prop -> Property
again :: forall prop. Testable prop => prop -> Property
again = (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ abort = False })
withMaxSuccess :: Testable prop => Int -> prop -> Property
withMaxSuccess :: forall prop. Testable prop => Int -> prop -> Property
withMaxSuccess Int
n = Int
n Int -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq` (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ maybeNumTests = Just n })
withDiscardRatio :: Testable prop => Int -> prop -> Property
withDiscardRatio :: forall prop. Testable prop => Int -> prop -> Property
withDiscardRatio Int
n = Int
n Int -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq` (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ maybeDiscardedRatio = Just n })
withMaxShrinks :: Testable prop => Int -> prop -> Property
withMaxShrinks :: forall prop. Testable prop => Int -> prop -> Property
withMaxShrinks Int
n = Int
n Int -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq` (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ maybeMaxShrinks = Just n })
withMaxSize :: Testable prop => Int -> prop -> Property
withMaxSize :: forall prop. Testable prop => Int -> prop -> Property
withMaxSize Int
n = Int
n Int -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq` (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ maybeMaxTestSize = Just n })
#ifndef NO_TYPEABLE
witness :: (Typeable a, Show a, Testable prop) => a -> prop -> Property
witness :: forall a prop.
(Typeable a, Show a, Testable prop) =>
a -> prop -> Property
witness a
a = a
a a -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq` (Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ theWitnesses = Wit a : theWitnesses res })
#endif
checkCoverage :: Testable prop => prop -> Property
checkCoverage :: forall prop. Testable prop => prop -> Property
checkCoverage = Confidence -> prop -> Property
forall prop. Testable prop => Confidence -> prop -> Property
checkCoverageWith Confidence
stdConfidence
checkCoverageWith :: Testable prop => Confidence -> prop -> Property
checkCoverageWith :: forall prop. Testable prop => Confidence -> prop -> Property
checkCoverageWith Confidence
confidence =
Confidence -> Integer
certainty Confidence
confidence Integer -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq`
Confidence -> Double
tolerance Confidence
confidence Double -> (prop -> Property) -> prop -> Property
forall a b. a -> b -> b
`seq`
(Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult (\Result
res -> Result
res{ maybeCheckCoverage = Just confidence })
stdConfidence :: Confidence
stdConfidence :: Confidence
stdConfidence =
Confidence {
certainty :: Integer
certainty = Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
9,
tolerance :: Double
tolerance = Double
0.9 }
label :: Testable prop => String -> prop -> Property
label :: forall prop. Testable prop => String -> prop -> Property
label String
s =
#ifndef NO_DEEPSEQ
String
s String -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq`
#endif
(Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult ((Result -> Result) -> prop -> Property)
-> (Result -> Result) -> prop -> Property
forall a b. (a -> b) -> a -> b
$
\Result
res -> Result
res { labels = s:labels res }
collect :: (Show a, Testable prop) => a -> prop -> Property
collect :: forall a prop. (Show a, Testable prop) => a -> prop -> Property
collect a
x = String -> prop -> Property
forall prop. Testable prop => String -> prop -> Property
label (a -> String
forall a. Show a => a -> String
show a
x)
classify :: Testable prop =>
Bool
-> String
-> prop -> Property
classify :: forall prop. Testable prop => Bool -> String -> prop -> Property
classify Bool
b String
s =
#ifndef NO_DEEPSEQ
String
s String -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq`
#endif
(Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult ((Result -> Result) -> prop -> Property)
-> (Result -> Result) -> prop -> Property
forall a b. (a -> b) -> a -> b
$
\Result
res -> Result
res { classes = (s, b):classes res }
cover :: Testable prop =>
Double
-> Bool
-> String
-> prop -> Property
cover :: forall prop.
Testable prop =>
Double -> Bool -> String -> prop -> Property
cover Double
p Bool
x String
s = (Result -> Result) -> Property -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult Result -> Result
f (Property -> Property) -> (prop -> Property) -> prop -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> String -> prop -> Property
forall prop. Testable prop => Bool -> String -> prop -> Property
classify Bool
x String
s
where
f :: Result -> Result
f Result
res = Result
res { requiredCoverage = (Nothing, s, p/100):requiredCoverage res }
tabulate :: Testable prop => String -> [String] -> prop -> Property
tabulate :: forall prop.
Testable prop =>
String -> [String] -> prop -> Property
tabulate String
key [String]
values =
#ifndef NO_DEEPSEQ
String
key String -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq` [String]
values [String] -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq`
#endif
(Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult ((Result -> Result) -> prop -> Property)
-> (Result -> Result) -> prop -> Property
forall a b. (a -> b) -> a -> b
$
\Result
res -> Result
res { tables = [(key, value) | value <- values] ++ tables res }
coverTable :: Testable prop =>
String -> [(String, Double)] -> prop -> Property
coverTable :: forall prop.
Testable prop =>
String -> [(String, Double)] -> prop -> Property
coverTable String
table [(String, Double)]
xs =
#ifndef NO_DEEPSEQ
String
table String -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq` [(String, Double)]
xs [(String, Double)] -> (prop -> Property) -> prop -> Property
forall a b. NFData a => a -> b -> b
`deepseq`
#endif
(Result -> Result) -> prop -> Property
forall prop.
Testable prop =>
(Result -> Result) -> prop -> Property
mapTotalResult ((Result -> Result) -> prop -> Property)
-> (Result -> Result) -> prop -> Property
forall a b. (a -> b) -> a -> b
$
\Result
res -> Result
res { requiredCoverage = ys ++ requiredCoverage res }
where
ys :: [(Maybe String, String, Double)]
ys = [(String -> Maybe String
forall a. a -> Maybe a
Just String
table, String
x, Double
pDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
100) | (String
x, Double
p) <- [(String, Double)]
xs]
(==>) :: Testable prop => Bool -> prop -> Property
Bool
False ==> :: forall prop. Testable prop => Bool -> prop -> Property
==> prop
_ = Discard -> Property
forall prop. Testable prop => prop -> Property
property Discard
Discard
Bool
True ==> prop
p = prop -> Property
forall prop. Testable prop => prop -> Property
property prop
p
within :: Testable prop => Int -> prop -> Property
within :: forall prop. Testable prop => Int -> prop -> Property
within Int
n = Result -> Int -> prop -> Property
forall prop. Testable prop => Result -> Int -> prop -> Property
onTimeout
(Result
failed { reason = "Timeout of " ++ show n ++ " microseconds exceeded." })
Int
n
discardAfter :: Testable prop => Int -> prop -> Property
discardAfter :: forall prop. Testable prop => Int -> prop -> Property
discardAfter Int
n = Result -> Int -> prop -> Property
forall prop. Testable prop => Result -> Int -> prop -> Property
onTimeout
(Result
rejected { reason = "Timeout of " ++ show n ++ " microseconds exceeded." })
Int
n
onTimeout :: Testable prop => Result -> Int -> prop -> Property
onTimeout :: forall prop. Testable prop => Result -> Int -> prop -> Property
onTimeout Result
timeoutResult Int
n = (Rose Result -> Rose Result) -> prop -> Property
forall prop.
Testable prop =>
(Rose Result -> Rose Result) -> prop -> Property
mapRoseResult Rose Result -> Rose Result
f
where
f :: Rose Result -> Rose Result
f Rose Result
rose = IO (Rose Result) -> Rose Result
ioRose (IO (Rose Result) -> Rose Result)
-> IO (Rose Result) -> Rose Result
forall a b. (a -> b) -> a -> b
$ do
let f (Maybe b)
m orError :: f (Maybe b) -> b -> f b
`orError` b
x = (Maybe b -> b) -> f (Maybe b) -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (b -> Maybe b -> b
forall a. a -> Maybe a -> a
fromMaybe b
x) f (Maybe b)
m
MkRose Result
res [Rose Result]
roses <- Int -> IO (Rose Result) -> IO (Maybe (Rose Result))
forall a. Int -> IO a -> IO (Maybe a)
timeout Int
n (Rose Result -> IO (Rose Result)
reduceRose Rose Result
rose) IO (Maybe (Rose Result)) -> Rose Result -> IO (Rose Result)
forall {f :: * -> *} {b}. Functor f => f (Maybe b) -> b -> f b
`orError`
Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
timeoutResult
Result
res' <- Int -> IO Result -> IO (Maybe Result)
forall a. Int -> IO a -> IO (Maybe a)
timeout Int
n (IO Result -> IO Result
protectResult (Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
res)) IO (Maybe Result) -> Result -> IO Result
forall {f :: * -> *} {b}. Functor f => f (Maybe b) -> b -> f b
`orError`
Result
timeoutResult
Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose Result
res' ((Rose Result -> Rose Result) -> [Rose Result] -> [Rose Result]
forall a b. (a -> b) -> [a] -> [b]
map Rose Result -> Rose Result
f [Rose Result]
roses))
#ifdef NO_TIMEOUT
timeout _ = fmap Just
#endif
forAll :: (Show a, Testable prop)
=> Gen a -> (a -> prop) -> Property
forAll :: forall a prop.
(Show a, Testable prop) =>
Gen a -> (a -> prop) -> Property
forAll Gen a
gen a -> prop
pf = Gen a -> (a -> [a]) -> (a -> prop) -> Property
forall a prop.
(Show a, Testable prop) =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrink Gen a
gen (\a
_ -> []) a -> prop
pf
forAllShow :: Testable prop
=> Gen a -> (a -> String) -> (a -> prop) -> Property
forAllShow :: forall prop a.
Testable prop =>
Gen a -> (a -> String) -> (a -> prop) -> Property
forAllShow Gen a
gen a -> String
shower a -> prop
pf = Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forAllShrinkShow Gen a
gen (\a
_ -> []) a -> String
shower a -> prop
pf
forAllBlind :: Testable prop
=> Gen a -> (a -> prop) -> Property
forAllBlind :: forall prop a. Testable prop => Gen a -> (a -> prop) -> Property
forAllBlind Gen a
gen a -> prop
pf = Gen a -> (a -> [a]) -> (a -> prop) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrinkBlind Gen a
gen (\a
_ -> []) a -> prop
pf
forAllShrink :: (Show a, Testable prop)
=> Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrink :: forall a prop.
(Show a, Testable prop) =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrink Gen a
gen a -> [a]
shrinker = Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forAllShrinkShow Gen a
gen a -> [a]
shrinker a -> String
forall a. Show a => a -> String
show
forAllShrinkShow
:: Testable prop
=> Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forAllShrinkShow :: forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
forAllShrinkShow Gen a
gen a -> [a]
shrinker a -> String
shower a -> prop
pf =
Gen a -> (a -> [a]) -> (a -> Property) -> Property
forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrinkBlind Gen a
gen a -> [a]
shrinker (\a
x -> String -> prop -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (a -> String
shower a
x) (a -> prop
pf a
x))
forAllShrinkBlind
:: Testable prop
=> Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrinkBlind :: forall prop a.
Testable prop =>
Gen a -> (a -> [a]) -> (a -> prop) -> Property
forAllShrinkBlind Gen a
gen a -> [a]
shrinker a -> prop
pf =
Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> Gen Prop -> Property
forall a b. (a -> b) -> a -> b
$
Gen a
gen Gen a -> (a -> Gen Prop) -> Gen Prop
forall a b. Gen a -> (a -> Gen b) -> Gen b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
x ->
Property -> Gen Prop
unProperty (Property -> Gen Prop) -> Property -> Gen Prop
forall a b. (a -> b) -> a -> b
$
(a -> [a]) -> a -> (a -> prop) -> Property
forall prop a.
Testable prop =>
(a -> [a]) -> a -> (a -> prop) -> Property
shrinking a -> [a]
shrinker a
x a -> prop
pf
(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
prop1
p1 .&. :: forall prop1 prop2.
(Testable prop1, Testable prop2) =>
prop1 -> prop2 -> Property
.&. prop2
p2 =
Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> Gen Prop -> Property
forall a b. (a -> b) -> a -> b
$
Gen Bool
forall a. Arbitrary a => Gen a
arbitrary Gen Bool -> (Bool -> Gen Prop) -> Gen Prop
forall a b. Gen a -> (a -> Gen b) -> Gen b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b ->
Property -> Gen Prop
unProperty (Property -> Gen Prop) -> Property -> Gen Prop
forall a b. (a -> b) -> a -> b
$
String -> Property -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (if Bool
b then String
"LHS" else String
"RHS") (Property -> Property) -> Property -> Property
forall a b. (a -> b) -> a -> b
$
if Bool
b then prop1 -> Property
forall prop. Testable prop => prop -> Property
property prop1
p1 else prop2 -> Property
forall prop. Testable prop => prop -> Property
property prop2
p2
(.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
prop1
p1 .&&. :: forall prop1 prop2.
(Testable prop1, Testable prop2) =>
prop1 -> prop2 -> Property
.&&. prop2
p2 = [Property] -> Property
forall prop. Testable prop => [prop] -> Property
conjoin [prop1 -> Property
forall prop. Testable prop => prop -> Property
property prop1
p1, prop2 -> Property
forall prop. Testable prop => prop -> Property
property prop2
p2]
conjoin :: Testable prop => [prop] -> Property
conjoin :: forall prop. Testable prop => [prop] -> Property
conjoin [prop]
ps =
Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> Gen Prop -> Property
forall a b. (a -> b) -> a -> b
$
do [Rose Result]
roses <- (prop -> Gen (Rose Result)) -> [prop] -> Gen [Rose Result]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Prop -> Rose Result) -> Gen Prop -> Gen (Rose Result)
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Rose Result
unProp (Gen Prop -> Gen (Rose Result))
-> (prop -> Gen Prop) -> prop -> Gen (Rose Result)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Property -> Gen Prop
unProperty (Property -> Gen Prop) -> (prop -> Property) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. prop -> Property
forall prop. Testable prop => prop -> Property
property) [prop]
ps
Prop -> Gen Prop
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rose Result -> Prop
MkProp ((Result -> Result) -> [Rose Result] -> Rose Result
conj Result -> Result
forall a. a -> a
id [Rose Result]
roses))
where
conj :: (Result -> Result) -> [Rose Result] -> Rose Result
conj Result -> Result
k [] =
Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose (Result -> Result
k Result
succeeded) []
conj Result -> Result
k (Rose Result
p : [Rose Result]
ps) = IO (Rose Result) -> Rose Result
forall a. IO (Rose a) -> Rose a
IORose (IO (Rose Result) -> Rose Result)
-> IO (Rose Result) -> Rose Result
forall a b. (a -> b) -> a -> b
$ do
rose :: Rose Result
rose@(MkRose Result
result [Rose Result]
_) <- Rose Result -> IO (Rose Result)
reduceRose Rose Result
p
case Result -> Maybe Bool
ok Result
result of
Maybe Bool
_ | Bool -> Bool
not (Result -> Bool
expect Result
result) ->
Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
failed { reason = "expectFailure may not occur inside a conjunction" })
Just Bool
True -> Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Result -> Result) -> [Rose Result] -> Rose Result
conj (Result -> Result -> Result
addLabels Result
result (Result -> Result) -> (Result -> Result) -> Result -> Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result -> Result -> Result
addCallbacksAndCoverage Result
result (Result -> Result) -> (Result -> Result) -> Result -> Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result -> Result
k) [Rose Result]
ps)
Just Bool
False -> Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rose Result
rose
Maybe Bool
Nothing -> do
rose2 :: Rose Result
rose2@(MkRose Result
result2 [Rose Result]
_) <- Rose Result -> IO (Rose Result)
reduceRose ((Result -> Result) -> [Rose Result] -> Rose Result
conj (Result -> Result -> Result
addCallbacksAndCoverage Result
result (Result -> Result) -> (Result -> Result) -> Result -> Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result -> Result
k) [Rose Result]
ps)
Rose Result -> IO (Rose Result)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rose Result -> IO (Rose Result))
-> Rose Result -> IO (Rose Result)
forall a b. (a -> b) -> a -> b
$
case Result -> Maybe Bool
ok Result
result2 of
Just Bool
True -> Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose (Result
result2 { ok = Nothing }) []
Just Bool
False -> Rose Result
rose2
Maybe Bool
Nothing -> Rose Result
rose2
addCallbacksAndCoverage :: Result -> Result -> Result
addCallbacksAndCoverage Result
result Result
r =
Result
r { callbacks = callbacks result ++ callbacks r,
requiredCoverage = requiredCoverage result ++ requiredCoverage r }
addLabels :: Result -> Result -> Result
addLabels Result
result Result
r =
Result
r { labels = labels result ++ labels r,
classes = classes result ++ classes r,
tables = tables result ++ tables r }
(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
prop1
p1 .||. :: forall prop1 prop2.
(Testable prop1, Testable prop2) =>
prop1 -> prop2 -> Property
.||. prop2
p2 = [Property] -> Property
forall prop. Testable prop => [prop] -> Property
disjoin [prop1 -> Property
forall prop. Testable prop => prop -> Property
property prop1
p1, prop2 -> Property
forall prop. Testable prop => prop -> Property
property prop2
p2]
disjoin :: Testable prop => [prop] -> Property
disjoin :: forall prop. Testable prop => [prop] -> Property
disjoin [prop]
ps =
Gen Prop -> Property
MkProperty (Gen Prop -> Property) -> Gen Prop -> Property
forall a b. (a -> b) -> a -> b
$
do [Rose Result]
roses <- (prop -> Gen (Rose Result)) -> [prop] -> Gen [Rose Result]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Prop -> Rose Result) -> Gen Prop -> Gen (Rose Result)
forall a b. (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Prop -> Rose Result
unProp (Gen Prop -> Gen (Rose Result))
-> (prop -> Gen Prop) -> prop -> Gen (Rose Result)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Property -> Gen Prop
unProperty (Property -> Gen Prop) -> (prop -> Property) -> prop -> Gen Prop
forall b c a. (b -> c) -> (a -> b) -> a -> c
. prop -> Property
forall prop. Testable prop => prop -> Property
property) [prop]
ps
Prop -> Gen Prop
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rose Result -> Prop
MkProp ((Rose Result -> Rose Result -> Rose Result)
-> Rose Result -> [Rose Result] -> Rose Result
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Rose Result -> Rose Result -> Rose Result
disj (Result -> [Rose Result] -> Rose Result
forall a. a -> [Rose a] -> Rose a
MkRose Result
failed []) [Rose Result]
roses))
where
disj :: Rose Result -> Rose Result -> Rose Result
disj :: Rose Result -> Rose Result -> Rose Result
disj Rose Result
p Rose Result
q =
do Result
result1 <- Rose Result
p
case Result -> Maybe Bool
ok Result
result1 of
Maybe Bool
_ | Bool -> Bool
not (Result -> Bool
expect Result
result1) -> Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
expectFailureError
Just Bool
False -> do
Result
result2 <- Rose Result
q
Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> Rose Result) -> Result -> Rose Result
forall a b. (a -> b) -> a -> b
$
case Result -> Maybe Bool
ok Result
result2 of
Maybe Bool
_ | Bool -> Bool
not (Result -> Bool
expect Result
result2) -> Result
expectFailureError
Just Bool
True -> Result -> Result -> Result
addCoverage Result
result1 Result
result2
Just Bool
False ->
MkResult {
ok :: Maybe Bool
ok = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False,
expect :: Bool
expect = Bool
True,
reason :: String
reason = String -> ShowS
sep (Result -> String
reason Result
result1) (Result -> String
reason Result
result2),
theException :: Maybe AnException
theException = Result -> Maybe AnException
theException Result
result1 Maybe AnException -> Maybe AnException -> Maybe AnException
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Result -> Maybe AnException
theException Result
result2,
abort :: Bool
abort = Bool
False,
maybeNumTests :: Maybe Int
maybeNumTests = Maybe Int
forall a. Maybe a
Nothing,
maybeCheckCoverage :: Maybe Confidence
maybeCheckCoverage = Maybe Confidence
forall a. Maybe a
Nothing,
maybeDiscardedRatio :: Maybe Int
maybeDiscardedRatio = Maybe Int
forall a. Maybe a
Nothing,
maybeMaxShrinks :: Maybe Int
maybeMaxShrinks = Maybe Int
forall a. Maybe a
Nothing,
maybeMaxTestSize :: Maybe Int
maybeMaxTestSize = Maybe Int
forall a. Maybe a
Nothing,
labels :: [String]
labels = [],
classes :: [(String, Bool)]
classes = [],
tables :: [(String, String)]
tables = [],
requiredCoverage :: [(Maybe String, String, Double)]
requiredCoverage = [],
callbacks :: [Callback]
callbacks =
Result -> [Callback]
callbacks Result
result1 [Callback] -> [Callback] -> [Callback]
forall a. [a] -> [a] -> [a]
++
[CallbackKind -> (State -> Result -> IO ()) -> Callback
PostFinalFailure CallbackKind
Counterexample ((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \State
st Result
_res -> Terminal -> String -> IO ()
putLine (State -> Terminal
terminal State
st) String
""] [Callback] -> [Callback] -> [Callback]
forall a. [a] -> [a] -> [a]
++
Result -> [Callback]
callbacks Result
result2,
testCase :: [String]
testCase =
Result -> [String]
testCase Result
result1 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
Result -> [String]
testCase Result
result2
WITNESSES(= theWitnesses result1 ++ theWitnesses result2)
}
Maybe Bool
Nothing -> Result
result2
Maybe Bool
_ -> Result -> Rose Result
forall a. a -> Rose a
forall (m :: * -> *) a. Monad m => a -> m a
return Result
result1
expectFailureError :: Result
expectFailureError = Result
failed { reason = "expectFailure may not occur inside a disjunction" }
sep :: String -> ShowS
sep [] String
s = String
s
sep String
s [] = String
s
sep String
s String
s' = String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s'
addCoverage :: Result -> Result -> Result
addCoverage Result
result Result
r =
Result
r { requiredCoverage = requiredCoverage result ++ requiredCoverage r }
infix 4 ===
(===) :: (Eq a, Show a) => a -> a -> Property
a
x === :: forall a. (Eq a, Show a) => a -> a -> Property
=== a
y =
String -> Bool -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (a -> String
forall a. Show a => a -> String
show a
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> String
interpret Bool
res String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
y) Bool
res
where
res :: Bool
res = a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y
interpret :: Bool -> String
interpret Bool
True = String
" == "
interpret Bool
False = String
" /= "
infix 4 =/=
(=/=) :: (Eq a, Show a) => a -> a -> Property
a
x =/= :: forall a. (Eq a, Show a) => a -> a -> Property
=/= a
y =
String -> Bool -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (a -> String
forall a. Show a => a -> String
show a
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> String
interpret Bool
res String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
y) Bool
res
where
res :: Bool
res = a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
y
interpret :: Bool -> String
interpret Bool
True = String
" /= "
interpret Bool
False = String
" == "
#ifndef NO_DEEPSEQ
total :: NFData a => a -> Property
total :: forall a. NFData a => a -> Property
total a
x = () -> Property
forall prop. Testable prop => prop -> Property
property (a -> ()
forall a. NFData a => a -> ()
rnf a
x)
#endif