hedgehog-0.4.1: Hedgehog will eat all your bugs.

Safe HaskellNone
LanguageHaskell98

Hedgehog.Internal.Property

Contents

Synopsis

Property

data Property Source #

A property test to check, along with some configurable limits like how many times to run the test.

Constructors

Property 

newtype TestLimit Source #

The number of successful tests that need to be run before a property test is considered successful.

Constructors

TestLimit Int 

Instances

Enum TestLimit Source # 
Eq TestLimit Source # 
Integral TestLimit Source # 
Num TestLimit Source # 
Ord TestLimit Source # 
Real TestLimit Source # 
Show TestLimit Source # 
Lift TestLimit Source # 

Methods

lift :: TestLimit -> Q Exp #

newtype DiscardLimit Source #

The number of discards to allow before giving up.

Constructors

DiscardLimit Int 

Instances

Enum DiscardLimit Source # 
Eq DiscardLimit Source # 
Integral DiscardLimit Source # 
Num DiscardLimit Source # 
Ord DiscardLimit Source # 
Real DiscardLimit Source # 
Show DiscardLimit Source # 
Lift DiscardLimit Source # 

Methods

lift :: DiscardLimit -> Q Exp #

newtype ShrinkLimit Source #

The number of shrinks to try before giving up on shrinking.

Constructors

ShrinkLimit Int 

Instances

Enum ShrinkLimit Source # 
Eq ShrinkLimit Source # 
Integral ShrinkLimit Source # 
Num ShrinkLimit Source # 
Ord ShrinkLimit Source # 
Real ShrinkLimit Source # 
Show ShrinkLimit Source # 
Lift ShrinkLimit Source # 

Methods

lift :: ShrinkLimit -> Q Exp #

property :: Test IO () -> Property Source #

Creates a property to check.

withTests :: TestLimit -> Property -> Property Source #

Set the number times a property should be executed before it is considered successful.

withDiscards :: DiscardLimit -> Property -> Property Source #

Set the number times a property is allowed to discard before the test runner gives up.

withShrinks :: ShrinkLimit -> Property -> Property Source #

Set the number times a property is allowed to shrink before the test runner gives up and prints the counterexample.

Group

data Group Source #

A named collection of property tests.

Constructors

Group 

Test

newtype Test m a Source #

A property test.

Constructors

Test 

Fields

Instances

MonadTrans Test Source # 

Methods

lift :: Monad m => m a -> Test m a #

Distributive Test Source # 

Associated Types

type Transformer (f :: (* -> *) -> * -> *) (Test :: (* -> *) -> * -> *) (m :: * -> *) :: Constraint Source #

Methods

distribute :: Transformer f Test m => Test (f m) a -> f (Test m) a Source #

MonadBase b m => MonadBase b (Test m) Source # 

Methods

liftBase :: b α -> Test m α #

MonadError e m => MonadError e (Test m) Source # 

Methods

throwError :: e -> Test m a #

catchError :: Test m a -> (e -> Test m a) -> Test m a #

MonadReader r m => MonadReader r (Test m) Source # 

Methods

ask :: Test m r #

local :: (r -> r) -> Test m a -> Test m a #

reader :: (r -> a) -> Test m a #

MonadState s m => MonadState s (Test m) Source # 

Methods

get :: Test m s #

put :: s -> Test m () #

state :: (s -> (a, s)) -> Test m a #

Monad m => Monad (Test m) Source # 

Methods

(>>=) :: Test m a -> (a -> Test m b) -> Test m b #

(>>) :: Test m a -> Test m b -> Test m b #

return :: a -> Test m a #

fail :: String -> Test m a #

Functor m => Functor (Test m) Source # 

Methods

fmap :: (a -> b) -> Test m a -> Test m b #

(<$) :: a -> Test m b -> Test m a #

Monad m => Applicative (Test m) Source # 

Methods

pure :: a -> Test m a #

(<*>) :: Test m (a -> b) -> Test m a -> Test m b #

(*>) :: Test m a -> Test m b -> Test m b #

(<*) :: Test m a -> Test m b -> Test m a #

MonadIO m => MonadIO (Test m) Source # 

Methods

liftIO :: IO a -> Test m a #

Monad m => Alternative (Test m) Source # 

Methods

empty :: Test m a #

(<|>) :: Test m a -> Test m a -> Test m a #

some :: Test m a -> Test m [a] #

many :: Test m a -> Test m [a] #

Monad m => MonadPlus (Test m) Source # 

Methods

mzero :: Test m a #

mplus :: Test m a -> Test m a -> Test m a #

MonadCatch m => MonadCatch (Test m) Source # 

Methods

catch :: Exception e => Test m a -> (e -> Test m a) -> Test m a #

MonadThrow m => MonadThrow (Test m) Source # 

Methods

throwM :: Exception e => e -> Test m a #

PrimMonad m => PrimMonad (Test m) Source # 

Associated Types

type PrimState (Test m :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (Test m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (Test m)), a#)) -> Test m a #

MonadResource m => MonadResource (Test m) Source # 

Methods

liftResourceT :: ResourceT IO a -> Test m a #

MFunctor * Test Source # 

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #

type Transformer t Test m Source # 
type PrimState (Test m) Source # 
type PrimState (Test m) = PrimState m

data Log Source #

Log messages which are recorded during a test run.

Instances

Eq Log Source # 

Methods

(==) :: Log -> Log -> Bool #

(/=) :: Log -> Log -> Bool #

Show Log Source # 

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

data Failure Source #

Details on where and why a test failed.

Constructors

Failure (Maybe Span) String (Maybe Diff) 

data Diff Source #

The difference between some expected and actual value.

Instances

Eq Diff Source # 

Methods

(==) :: Diff -> Diff -> Bool #

(/=) :: Diff -> Diff -> Bool #

Show Diff Source # 

Methods

showsPrec :: Int -> Diff -> ShowS #

show :: Diff -> String #

showList :: [Diff] -> ShowS #

forAll :: (Monad m, Show a, HasCallStack) => Gen m a -> Test m a Source #

Generates a random input for the test by running the provided generator.

forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen m a -> Test m a Source #

Generates a random input for the test by running the provided generator.

This is a the same as forAll but allows the user to provide a custom rendering function. This is useful for values which don't have a Show instance.

annotate :: (Monad m, HasCallStack) => String -> Test m () Source #

Annotates the source code with a message that might be useful for debugging a test failure.

annotateShow :: (Monad m, Show a, HasCallStack) => a -> Test m () Source #

Annotates the source code with a value that might be useful for debugging a test failure.

footnote :: Monad m => String -> Test m () Source #

Logs a message to be displayed as additional information in the footer of the failure report.

footnoteShow :: (Monad m, Show a) => a -> Test m () Source #

Logs a value to be displayed as additional information in the footer of the failure report.

discard :: Monad m => Test m a Source #

Discards a test entirely.

failure :: (Monad m, HasCallStack) => Test m a Source #

Causes a test to fail.

success :: Monad m => Test m () Source #

Another name for pure ().

assert :: (Monad m, HasCallStack) => Bool -> Test m () Source #

Fails the test if the condition provided is False.

(===) :: (Monad m, Eq a, Show a, HasCallStack) => a -> a -> Test m () infix 4 Source #

Fails the test if the two arguments provided are not equal.

liftCatch :: (MonadCatch m, HasCallStack) => m a -> Test m a Source #

Fails the test if the action throws an exception.

/The benefit of using this over lift is that the location of the exception will be shown in the output./

liftCatchIO :: (MonadIO m, HasCallStack) => IO a -> Test m a Source #

Fails the test if the action throws an exception.

/The benefit of using this over liftIO is that the location of the exception will be shown in the output./

liftEither :: (Monad m, Show x, HasCallStack) => Either x a -> Test m a Source #

Fails the test if the Either is Left, otherwise returns the value in the Right.

liftExceptT :: (Monad m, Show x, HasCallStack) => ExceptT x m a -> Test m a Source #

Fails the test if the ExceptT is Left, otherwise returns the value in the Right.

withCatch :: (MonadCatch m, HasCallStack) => Test m a -> Test m a Source #

Fails the test if the action throws an exception.

/The benefit of using this over simply letting the exception bubble up is that the location of the closest withCatch will be shown in the output./

withExceptT :: (Monad m, Show x, HasCallStack) => Test (ExceptT x m) a -> Test m a Source #

Fails the test if the ExceptT is Left, otherwise returns the value in the Right.

withResourceT :: MonadResourceBase m => Test (ResourceT m) a -> Test m a Source #

Run a computation which requires resource acquisition / release.

Note that if you allocate anything before a forAll you will likely encounter unexpected behaviour, due to the way ResourceT interacts with the control flow introduced by shrinking.

Internal

These functions are exported in case you need them in a pinch, but are not part of the public API and may change at any time, even as part of a minor update.

defaultConfig :: PropertyConfig Source #

The default configuration for a property test.

mapConfig :: (PropertyConfig -> PropertyConfig) -> Property -> Property Source #

Map a config modification function over a property.

failWith :: (Monad m, HasCallStack) => Maybe Diff -> String -> Test m a Source #

Fail with an error message, useful for building other failure combinators.

writeLog :: Monad m => Log -> Test m () Source #

runTest :: Test m a -> Gen m (Either Failure a, [Log]) Source #