hedgehog-1.0.1: Release with confidence.

Safe HaskellNone
LanguageHaskell98

Hedgehog.Internal.Property

Contents

Synopsis

Property

data Property Source #

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

newtype PropertyT m a Source #

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

Constructors

PropertyT 

Fields

Instances
MonadTrans PropertyT Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadTransDistributive PropertyT Source # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type Transformer f PropertyT m :: Constraint Source #

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

liftBase :: b α -> PropertyT m α #

MonadState s m => MonadState s (PropertyT m) Source # 
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) Source # 
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) Source # 
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) Source # 
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) Source # 
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 => MonadFail (PropertyT m) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fail :: String -> PropertyT m a #

Monad m => Applicative (PropertyT m) Source # 
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) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> PropertyT m a #

MonadPlus m => Alternative (PropertyT m) Source # 
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) Source # 
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) Source # 
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) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

PrimMonad m => PrimMonad (PropertyT m) Source # 
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 #

MonadResource m => MonadResource (PropertyT m) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> PropertyT m a Source #

MFunctor PropertyT Source # 
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 Source # 
Instance details

Defined in Hedgehog.Internal.Property

type PrimState (PropertyT m) Source # 
Instance details

Defined in Hedgehog.Internal.Property

newtype PropertyName Source #

The name of a property.

Should be constructed using OverloadedStrings:

  "apples" :: PropertyName

Constructors

PropertyName 

newtype TestLimit Source #

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 Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Lift TestLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: TestLimit -> Q Exp #

newtype TestCount Source #

The number of tests a property ran successfully.

Constructors

TestCount Int 
Instances
Enum TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show TestCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

newtype DiscardLimit Source #

The number of discards to allow before giving up.

Can be constructed using numeric literals:

  10000 :: DiscardLimit

Constructors

DiscardLimit Int 
Instances
Enum DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Lift DiscardLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: DiscardLimit -> Q Exp #

newtype DiscardCount Source #

The number of tests a property had to discard.

Constructors

DiscardCount Int 
Instances
Enum DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show DiscardCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

newtype ShrinkLimit Source #

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 Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Lift ShrinkLimit Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: ShrinkLimit -> Q Exp #

newtype ShrinkCount Source #

The numbers of times a property was able to shrink after a failing test.

Constructors

ShrinkCount Int 
Instances
Enum ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

newtype ShrinkRetries Source #

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 Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Lift ShrinkRetries Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: ShrinkRetries -> Q Exp #

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

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 Source #

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

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

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 Source #

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 Source #

Creates a property with the default configuration.

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

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.

An example where this is useful is parallel state machine testing, as executeParallel requires MonadBaseControl IO in order to be able to spawn threads in MonadTest.

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

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

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

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

forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen a -> PropertyT 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.

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

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 Source #

Discards the current test entirely.

Group

data Group Source #

A named collection of property tests.

Constructors

Group 

newtype GroupName Source #

The name of a group of properties.

Should be constructed using OverloadedStrings:

  "fruit" :: GroupName

Constructors

GroupName 

Fields

newtype PropertyCount Source #

The number of properties in a group.

Constructors

PropertyCount Int 
Instances
Enum PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Eq PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Integral PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Real PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show PropertyCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

TestT

class Monad m => MonadTest m where Source #

Methods

liftTest :: Test a -> m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> MaybeT m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> ResourceT m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> TestT m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> PropertyT m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> IdentityT m a Source #

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

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

type Test = TestT Identity Source #

A test monad allows the assertion of expectations.

newtype TestT m a Source #

A test monad transformer allows the assertion of expectations.

Constructors

TestT 
Instances
MonadTrans TestT Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadTransControl TestT Source # 
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 #

MonadTransDistributive TestT Source # 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type Transformer f TestT m :: Constraint Source #

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

liftBase :: b α -> TestT m α #

MonadBaseControl b m => MonadBaseControl b (TestT m) Source # 
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) Source # 
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) Source # 
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) Source # 
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) Source # 
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) Source # 
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 => MonadFail (TestT m) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fail :: String -> TestT m a #

Monad m => Applicative (TestT m) Source # 
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) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> TestT m a #

MonadCatch m => MonadCatch (TestT m) Source # 
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) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

PrimMonad m => PrimMonad (TestT m) Source # 
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) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Defined in Hedgehog.Internal.Property

Methods

liftTest :: Test a -> TestT m a Source #

MFunctor TestT Source # 
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 Source # 
Instance details

Defined in Hedgehog.Internal.Property

type Transformer t TestT m Source # 
Instance details

Defined in Hedgehog.Internal.Property

type PrimState (TestT m) Source # 
Instance details

Defined in Hedgehog.Internal.Property

type StM (TestT m) a Source # 
Instance details

Defined in Hedgehog.Internal.Property

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

data Log Source #

Log messages which are recorded during a test run.

Instances
Eq Log Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Log Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

newtype Journal Source #

A record containing the details of a test run.

Constructors

Journal 

Fields

Instances
Eq Journal Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Journal Source # 
Instance details

Defined in Hedgehog.Internal.Property

Semigroup Journal Source # 
Instance details

Defined in Hedgehog.Internal.Property

Monoid Journal Source # 
Instance details

Defined in Hedgehog.Internal.Property

data Failure Source #

Details on where and why a test failed.

Constructors

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

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Failure Source # 
Instance details

Defined in Hedgehog.Internal.Property

data Diff Source #

The difference between some expected and actual value.

Instances
Eq Diff Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Show Diff Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Diff -> ShowS #

show :: Diff -> String #

showList :: [Diff] -> ShowS #

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

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

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

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

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

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

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

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

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

Causes a test to fail.

success :: MonadTest m => m () Source #

Another name for pure ().

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

Fails the test if the condition provided is False.

diff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> (a -> b -> Bool) -> b -> m () Source #

Fails the test and shows a git-like diff if the comparison operation evaluates to False when applied to its arguments.

The comparison function is the second argument, which may be counter-intuitive to Haskell programmers. However, it allows operators to be written infix for easy reading:

  diff y (<) 87
  diff x (<=) r

/This function behaves like the unix diff tool, which gives a `0` exit code if the compared files are identical, or a `1` exit code code otherwise. Like unix diff, if the arguments fail the comparison, a diff is shown./

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

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

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

Fails the test if the two arguments provided are equal.

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

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

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

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 Source #

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 Source #

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

Coverage

newtype Coverage a Source #

The extent to which all classifiers cover a test.

/When a given classification's coverage does not exceed the required minimum, the test will be failed./

Constructors

Coverage 
Instances
Functor Coverage Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fmap :: (a -> b) -> Coverage a -> Coverage b #

(<$) :: a -> Coverage b -> Coverage a #

Foldable Coverage Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fold :: Monoid m => Coverage m -> m #

foldMap :: Monoid m => (a -> m) -> Coverage a -> m #

foldr :: (a -> b -> b) -> b -> Coverage a -> b #

foldr' :: (a -> b -> b) -> b -> Coverage a -> b #

foldl :: (b -> a -> b) -> b -> Coverage a -> b #

foldl' :: (b -> a -> b) -> b -> Coverage a -> b #

foldr1 :: (a -> a -> a) -> Coverage a -> a #

foldl1 :: (a -> a -> a) -> Coverage a -> a #

toList :: Coverage a -> [a] #

null :: Coverage a -> Bool #

length :: Coverage a -> Int #

elem :: Eq a => a -> Coverage a -> Bool #

maximum :: Ord a => Coverage a -> a #

minimum :: Ord a => Coverage a -> a #

sum :: Num a => Coverage a -> a #

product :: Num a => Coverage a -> a #

Traversable Coverage Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

traverse :: Applicative f => (a -> f b) -> Coverage a -> f (Coverage b) #

sequenceA :: Applicative f => Coverage (f a) -> f (Coverage a) #

mapM :: Monad m => (a -> m b) -> Coverage a -> m (Coverage b) #

sequence :: Monad m => Coverage (m a) -> m (Coverage a) #

Eq a => Eq (Coverage a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

(==) :: Coverage a -> Coverage a -> Bool #

(/=) :: Coverage a -> Coverage a -> Bool #

Show a => Show (Coverage a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Coverage a -> ShowS #

show :: Coverage a -> String #

showList :: [Coverage a] -> ShowS #

Semigroup a => Semigroup (Coverage a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

(<>) :: Coverage a -> Coverage a -> Coverage a #

sconcat :: NonEmpty (Coverage a) -> Coverage a #

stimes :: Integral b => b -> Coverage a -> Coverage a #

(Semigroup a, Monoid a) => Monoid (Coverage a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

mempty :: Coverage a #

mappend :: Coverage a -> Coverage a -> Coverage a #

mconcat :: [Coverage a] -> Coverage a #

data Label a Source #

The extent to which a test is covered by a classifier.

/When a classifier's coverage does not exceed the required minimum, the test will be failed./

Instances
Functor Label Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fmap :: (a -> b) -> Label a -> Label b #

(<$) :: a -> Label b -> Label a #

Foldable Label Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

fold :: Monoid m => Label m -> m #

foldMap :: Monoid m => (a -> m) -> Label a -> m #

foldr :: (a -> b -> b) -> b -> Label a -> b #

foldr' :: (a -> b -> b) -> b -> Label a -> b #

foldl :: (b -> a -> b) -> b -> Label a -> b #

foldl' :: (b -> a -> b) -> b -> Label a -> b #

foldr1 :: (a -> a -> a) -> Label a -> a #

foldl1 :: (a -> a -> a) -> Label a -> a #

toList :: Label a -> [a] #

null :: Label a -> Bool #

length :: Label a -> Int #

elem :: Eq a => a -> Label a -> Bool #

maximum :: Ord a => Label a -> a #

minimum :: Ord a => Label a -> a #

sum :: Num a => Label a -> a #

product :: Num a => Label a -> a #

Traversable Label Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

traverse :: Applicative f => (a -> f b) -> Label a -> f (Label b) #

sequenceA :: Applicative f => Label (f a) -> f (Label a) #

mapM :: Monad m => (a -> m b) -> Label a -> m (Label b) #

sequence :: Monad m => Label (m a) -> m (Label a) #

Eq a => Eq (Label a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

(==) :: Label a -> Label a -> Bool #

(/=) :: Label a -> Label a -> Bool #

Show a => Show (Label a) Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

Semigroup a => Semigroup (Label a) Source #

This semigroup is right biased. The name, location and percentage from the rightmost Log will be kept. This shouldn't be a problem since the library doesn't allow setting multiple classes with the same ClassifierName.

Instance details

Defined in Hedgehog.Internal.Property

Methods

(<>) :: Label a -> Label a -> Label a #

sconcat :: NonEmpty (Label a) -> Label a #

stimes :: Integral b => b -> Label a -> Label a #

newtype LabelName Source #

The name of a classifier.

Should be constructed using OverloadedStrings:

  "apples" :: LabelName

Constructors

LabelName 

Fields

cover :: (MonadTest m, HasCallStack) => CoverPercentage -> LabelName -> Bool -> m () Source #

Require a certain percentage of the tests to be covered by the classifier.

   prop_with_coverage :: Property
   prop_with_coverage =
     property $ do
       match <- forAll Gen.bool
       cover 30 True $ match
       cover 30 False $ not match

The example above requires a minimum of 30% coverage for both classifiers. If these requirements are not met, it will fail the test.

classify :: (MonadTest m, HasCallStack) => LabelName -> Bool -> m () Source #

Records the proportion of tests which satisfy a given condition.

   prop_with_classifier :: Property
   prop_with_classifier =
     property $ do
       xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha
       for_ xs $ x -> do
         classify "newborns" $ x == 0
         classify "children" $ x > 0 && x < 13
         classify "teens" $ x > 12 && x < 20

label :: (MonadTest m, HasCallStack) => LabelName -> m () Source #

Add a label for each test run. It produces a table showing the percentage of test runs that produced each label.

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

Like label, but uses Show to render its argument for display.

data Cover Source #

Whether a test is covered by a classifier, and therefore belongs to a Class.

Constructors

NoCover 
Cover 
Instances
Eq Cover Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

Ord Cover Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

compare :: Cover -> Cover -> Ordering #

(<) :: Cover -> Cover -> Bool #

(<=) :: Cover -> Cover -> Bool #

(>) :: Cover -> Cover -> Bool #

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

max :: Cover -> Cover -> Cover #

min :: Cover -> Cover -> Cover #

Show Cover Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

showsPrec :: Int -> Cover -> ShowS #

show :: Cover -> String #

showList :: [Cover] -> ShowS #

Semigroup Cover Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

(<>) :: Cover -> Cover -> Cover #

sconcat :: NonEmpty Cover -> Cover #

stimes :: Integral b => b -> Cover -> Cover #

Monoid Cover Source # 
Instance details

Defined in Hedgehog.Internal.Property

Methods

mempty :: Cover #

mappend :: Cover -> Cover -> Cover #

mconcat :: [Cover] -> Cover #

newtype CoverCount Source #

The total number of tests which are covered by a classifier.

Can be constructed using numeric literals:

  30 :: CoverCount

Constructors

CoverCount 

Fields

Instances
Eq CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Num CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Ord CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Show CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Semigroup CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

Monoid CoverCount Source # 
Instance details

Defined in Hedgehog.Internal.Property

newtype CoverPercentage Source #

The relative number of tests which are covered by a classifier.

Can be constructed using numeric literals:

  30 :: CoverPercentage

Constructors

CoverPercentage 

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.

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

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

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

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

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

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

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

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