hedgehog-0.6.1: Hedgehog will eat all your bugs.

Safe HaskellNone
LanguageHaskell98

Hedgehog.Internal.Property

Contents

Synopsis

Property

data Property #

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

newtype PropertyT m a #

The property monad transformer allows both the generation of test inputs and the assertion of expectations.

Constructors

PropertyT 

Fields

Instances
MonadTrans PropertyT # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

Distributive PropertyT # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type Transformer f PropertyT m :: Constraint #

Methods

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

MonadBase b m => MonadBase b (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftBase :: b α -> PropertyT m α #

MonadState s m => MonadState s (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

get :: PropertyT m s #

put :: s -> PropertyT m () #

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

MonadReader r m => MonadReader r (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

ask :: PropertyT m r #

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

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

MonadError e m => MonadError e (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

throwError :: e -> PropertyT m a #

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

Monad m => Monad (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

return :: a -> PropertyT m a #

fail :: String -> PropertyT m a #

Functor m => Functor (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Monad m => Applicative (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

pure :: a -> PropertyT m a #

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

liftA2 :: (a -> b -> c) -> PropertyT m a -> PropertyT m b -> PropertyT m c #

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

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

MonadIO m => MonadIO (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> PropertyT m a #

MonadPlus m => Alternative (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

empty :: PropertyT m a #

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

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

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

MonadPlus m => MonadPlus (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

mzero :: PropertyT m a #

mplus :: PropertyT m a -> PropertyT m a -> PropertyT m a #

MonadCatch m => MonadCatch (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadThrow m => MonadThrow (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

PrimMonad m => PrimMonad (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState (PropertyT m) :: Type #

Methods

primitive :: (State# (PrimState (PropertyT m)) -> (#State# (PrimState (PropertyT m)), a#)) -> PropertyT m a #

Monad m => MonadTest (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> PropertyT m a #

MFunctor PropertyT # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

type Transformer t PropertyT m # 
Instance details

Defined in Hedgehog.Internal.Property

type PrimState (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

newtype PropertyName #

The name of a property.

Can be constructed using OverloadedStrings:

  "apples" :: PropertyName

Constructors

PropertyName 

newtype TestLimit #

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

Can be constructed using numeric literals:

  200 :: TestLimit

Constructors

TestLimit Int 
Instances
Enum TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Eq TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Integral TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Num TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Ord TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Real TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Show TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Lift TestLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: TestLimit -> Q Exp #

newtype DiscardLimit #

The number of discards to allow before giving up.

Can be constructed using numeric literals:

  10000 :: DiscardLimit

Constructors

DiscardLimit Int 
Instances
Enum DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Eq DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Integral DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Num DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Ord DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Real DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Show DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Lift DiscardLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: DiscardLimit -> Q Exp #

newtype ShrinkLimit #

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

Can be constructed using numeric literals:

  1000 :: ShrinkLimit

Constructors

ShrinkLimit Int 
Instances
Enum ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Eq ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Integral ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Num ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Ord ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Real ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Lift ShrinkLimit # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: ShrinkLimit -> Q Exp #

newtype ShrinkRetries #

The number of times to re-run a test during shrinking. This is useful if you are testing something which fails non-deterministically and you want to increase the change of getting a good shrink.

If you are doing parallel state machine testing, you should probably set shrink retries to something like 10. This will mean that during shrinking, a parallel test case requires 10 successful runs before it is passes and we try a different shrink.

Can be constructed using numeric literals:

  0 :: ShrinkRetries

Constructors

ShrinkRetries Int 
Instances
Enum ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Eq ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Integral ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Num ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Ord ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Real ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Lift ShrinkRetries # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: ShrinkRetries -> Q Exp #

withTests :: TestLimit -> Property -> Property #

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

If you have a test that does not involve any generators and thus does not need to run repeatedly, you can use withTests 1 to define a property that will only be checked once.

withDiscards :: DiscardLimit -> Property -> Property #

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

withShrinks :: ShrinkLimit -> Property -> Property #

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

withRetries :: ShrinkRetries -> Property -> Property #

Set the number of times a property will be executed for each shrink before the test runner gives up and tries a different shrink. See ShrinkRetries for more information.

property :: HasCallStack => PropertyT IO () -> Property #

Creates a property with the default configuration.

test :: Monad m => TestT m a -> PropertyT m a #

Lift a test in to a property.

Because both TestT and PropertyT have MonadTest instances, this function is not often required. It can however be useful for writing functions directly in TestT and thus gaining a MonadTransControl instance at the expense of not being able to generate additional inputs using forAll.

One use case for this is writing tests which use ResourceT:

  property $ do
    n <- forAll $ Gen.int64 Range.linearBounded
    test . runResourceT $ do
      -- test with resource usage here

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

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

forAllT :: (Monad m, Show a, HasCallStack) => GenT m a -> PropertyT m a #

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

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

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.

forAllWithT :: (Monad m, HasCallStack) => (a -> String) -> GenT m a -> PropertyT m a #

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

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

discard :: Monad m => PropertyT m a #

Discards the current test entirely.

Group

data Group #

A named collection of property tests.

Constructors

Group 

newtype GroupName #

The name of a group of properties.

Can be constructed using OverloadedStrings:

  "fruit" :: GroupName

Constructors

GroupName 

Fields

TestT

class Monad m => MonadTest m where #

Methods

liftTest :: Test a -> m a #

Instances
MonadTest m => MonadTest (MaybeT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> MaybeT m a #

MonadTest m => MonadTest (ResourceT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> ResourceT m a #

Monad m => MonadTest (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> TestT m a #

Monad m => MonadTest (PropertyT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> PropertyT m a #

MonadTest m => MonadTest (ExceptT x m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> ExceptT x m a #

(MonadTest m, Monoid w) => MonadTest (WriterT w m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> WriterT w m a #

MonadTest m => MonadTest (StateT s m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> StateT s m a #

MonadTest m => MonadTest (ReaderT r m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> ReaderT r m a #

MonadTest m => MonadTest (IdentityT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> IdentityT m a #

MonadTest m => MonadTest (StateT s m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> StateT s m a #

(MonadTest m, Monoid w) => MonadTest (WriterT w m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> WriterT w m a #

MonadTest m => MonadTest (ContT r m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> ContT r m a #

(MonadTest m, Monoid w) => MonadTest (RWST r w s m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> RWST r w s m a #

(MonadTest m, Monoid w) => MonadTest (RWST r w s m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> RWST r w s m a #

type Test = TestT Identity #

A test monad allows the assertion of expectations.

newtype TestT m a #

A test monad transformer allows the assertion of expectations.

Constructors

TestT 

Fields

Instances
MonadTrans TestT # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadTransControl TestT # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type StT TestT a :: Type #

Methods

liftWith :: Monad m => (Run TestT -> m a) -> TestT m a #

restoreT :: Monad m => m (StT TestT a) -> TestT m a #

Distributive TestT # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type Transformer f TestT m :: Constraint #

Methods

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

MonadBase b m => MonadBase b (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftBase :: b α -> TestT m α #

MonadBaseControl b m => MonadBaseControl b (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type StM (TestT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (TestT m) b -> b a) -> TestT m a #

restoreM :: StM (TestT m) a -> TestT m a #

MonadState s m => MonadState s (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

get :: TestT m s #

put :: s -> TestT m () #

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

MonadReader r m => MonadReader r (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

ask :: TestT m r #

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

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

MonadError e m => MonadError e (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

throwError :: e -> TestT m a #

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

Monad m => Monad (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

return :: a -> TestT m a #

fail :: String -> TestT m a #

Functor m => Functor (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Monad m => Applicative (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

pure :: a -> TestT m a #

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

liftA2 :: (a -> b -> c) -> TestT m a -> TestT m b -> TestT m c #

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

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

MonadIO m => MonadIO (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> TestT m a #

MonadCatch m => MonadCatch (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadThrow m => MonadThrow (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

PrimMonad m => PrimMonad (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState (TestT m) :: Type #

Methods

primitive :: (State# (PrimState (TestT m)) -> (#State# (PrimState (TestT m)), a#)) -> TestT m a #

MonadResource m => MonadResource (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

Monad m => MonadTest (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> TestT m a #

MFunctor TestT # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

type StT TestT a # 
Instance details

Defined in Hedgehog.Internal.Property

type StT TestT a = (Either Failure a, [Log])
type Transformer t TestT m # 
Instance details

Defined in Hedgehog.Internal.Property

type PrimState (TestT m) # 
Instance details

Defined in Hedgehog.Internal.Property

type StM (TestT m) a # 
Instance details

Defined in Hedgehog.Internal.Property

type StM (TestT m) a = ComposeSt TestT m a

data Log #

Log messages which are recorded during a test run.

Instances
Eq Log # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Log # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

data Failure #

Details on where and why a test failed.

Constructors

Failure (Maybe Span) String (Maybe Diff) 
Instances
Eq Failure # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Failure # 
Instance details

Defined in Hedgehog.Internal.Property

data Diff #

The difference between some expected and actual value.

Instances
Eq Diff # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Diff # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Diff -> ShowS #

show :: Diff -> String #

showList :: [Diff] -> ShowS #

annotate :: (MonadTest m, HasCallStack) => String -> m () #

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

annotateShow :: (MonadTest m, Show a, HasCallStack) => a -> m () #

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

footnote :: MonadTest m => String -> m () #

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

footnoteShow :: (MonadTest m, Show a) => a -> m () #

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

failure :: (MonadTest m, HasCallStack) => m a #

Causes a test to fail.

success :: MonadTest m => m () #

Another name for pure ().

assert :: (MonadTest m, HasCallStack) => Bool -> m () #

Fails the test if the condition provided is False.

(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #

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

(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #

Fails the test if the two arguments provided are equal.

eval :: (MonadTest m, HasCallStack) => a -> m a #

Fails the test if the value throws an exception when evaluated to weak head normal form (WHNF).

evalM :: (MonadTest m, MonadCatch m, HasCallStack) => m a -> m a #

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 evalM will be shown in the output.

evalIO :: (MonadTest m, MonadIO m, HasCallStack) => IO a -> m a #

Fails the test if the IO action throws an exception.

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

evalEither :: (MonadTest m, Show x, HasCallStack) => Either x a -> m a #

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

evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a #

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

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 #

The default configuration for a property test.

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

Map a config modification function over a property.

failDiff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> b -> m () #

Fails with an error which shows the difference between two values.

failException :: (MonadTest m, HasCallStack) => SomeException -> m a #

Fails with an error which renders the type of an exception and its error message.

failWith :: (MonadTest m, HasCallStack) => Maybe Diff -> String -> m a #

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

writeLog :: MonadTest m => Log -> m () #

Log some information which might be relevant to a potential test failure.

mkTest :: (Either Failure a, [Log]) -> Test a #

mkTestT :: m (Either Failure a, [Log]) -> TestT m a #

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

runTestT :: TestT m a -> m (Either Failure a, [Log]) #