hedgehog-1.2: Release with confidence.
Safe Haskell None
Language Haskell2010

Hedgehog.Internal.Property

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

Instances

Instances details
MonadTrans PropertyT Source #
Instance details

Defined in Hedgehog.Internal.Property

MonadTransDistributive PropertyT Source #
Instance details

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

Methods

liftBase :: b α -> PropertyT m α Source #

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

Defined in Hedgehog.Internal.Property

Associated Types

type StM ( PropertyT m) a Source #

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState ( PropertyT m) Source #

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

MFunctor PropertyT Source #
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

type StM ( PropertyT m) a Source #
Instance details

Defined in Hedgehog.Internal.Property

newtype PropertyName Source #

The name of a property.

Should be constructed using OverloadedStrings :

  "apples" :: PropertyName

Instances

Instances details
Eq PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

Ord PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

Show PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

IsString PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

Semigroup PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

Lift PropertyName Source #
Instance details

Defined in Hedgehog.Internal.Property

data PropertyConfig Source #

Configuration for a property test.

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

Instances details
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

newtype TestCount Source #

The number of tests a property ran successfully.

Constructors

TestCount Int

Instances

Instances details
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

Lift 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

Instances

Instances details
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

newtype DiscardCount Source #

The number of tests a property had to discard.

Instances

Instances details
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

Instances details
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

newtype ShrinkCount Source #

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

Constructors

ShrinkCount Int

Instances

Instances details
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

data Skip Source #

Where to start running a property's tests.

Constructors

SkipNothing

Don't skip anything.

SkipToTest TestCount

Skip to a specific test number. If it fails, shrink as normal. If it passes, move on to the next test. Coverage checks are disabled.

SkipToShrink TestCount ShrinkPath

Skip to a specific test number and shrink state. If it fails, stop without shrinking further. If it passes, the property will pass without running any more tests.

Due to implementation details, all intermediate shrink states - those on the direct path from the original test input to the target state - will be tested too, and their results discarded.

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

Instances

Instances details
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

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.

withSkip :: Skip -> Property -> Property Source #

Set the target that a property will skip to before it starts to run.

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.

defaultMinTests :: TestLimit Source #

The minimum amount of tests to run for a Property

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

Discards the current test entirely.

skipCompress :: Skip -> String Source #

Compress a Skip into a hopefully-short alphanumeric string.

The bit that might be long is the ShrinkPath in SkipToShrink . For that, we encode the path components in base 26, alternating between uppercase and lowercase alphabets to distinguish list elements. Additionally when we have runs of equal components, we use the normal base 10 encoding to indicate the length.

This gives something which is hopefully quite short, but a human can roughly interpret it by eyeball.

shrinkPathCompress :: ShrinkPath -> String Source #

Compress a ShrinkPath into a hopefully-short alphanumeric string.

We encode the path components in base 26, alternating between uppercase and lowercase alphabets to distinguish list elements. Additionally when we have runs of equal components, we use the normal base 10 encoding to indicate the length.

skipDecompress :: String -> Maybe Skip Source #

Decompress a Skip .

This satisfies

  skipDecompress (skipCompress a) == Just a

shrinkPathDecompress :: String -> Maybe ShrinkPath Source #

Decompress a ShrinkPath .

This satisfies

  shrinkPathDecompress (shrinkPathCompress a) == Just a

Group

data Group Source #

A named collection of property tests.

newtype GroupName Source #

The name of a group of properties.

Should be constructed using OverloadedStrings :

  "fruit" :: GroupName

newtype PropertyCount Source #

The number of properties in a group.

Instances

Instances details
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 #

Instances

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

( 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.

Instances

Instances details
MonadTrans TestT Source #
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

MonadTransControl TestT Source #
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type StT TestT a Source #

MonadTransDistributive TestT Source #
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type Transformer f TestT m Source #

Methods

distributeT :: forall f (m :: Type -> Type ) a. 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 α Source #

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

Defined in Hedgehog.Internal.Property

Associated Types

type StM ( TestT m) a Source #

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

Methods

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

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

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState ( TestT m) Source #

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

MFunctor TestT Source #
Instance details

Defined in Hedgehog.Internal.Property

Methods

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

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

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).

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

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

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 .

evalEitherM :: ( MonadTest m, Show x, MonadCatch m, HasCallStack ) => m ( Either x a) -> m a Source #

Fails the test if the action throws an exception, or 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 .

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

Fails the test if the Maybe is Nothing , otherwise returns the value in the Just .

evalMaybeM :: ( MonadTest m, Show a, MonadCatch m, HasCallStack ) => m ( Maybe a) -> m a Source #

Fails the test if the action throws an exception, or if the Maybe is Nothing , otherwise returns the value in the Just .

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.

Instances

Instances details
Functor Coverage Source #
Instance details

Defined in Hedgehog.Internal.Property

Foldable Coverage Source #
Instance details

Defined in Hedgehog.Internal.Property

Traversable Coverage Source #
Instance details

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Instances details
Functor Label Source #
Instance details

Defined in Hedgehog.Internal.Property

Foldable Label Source #
Instance details

Defined in Hedgehog.Internal.Property

Traversable Label Source #
Instance details

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

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

Defined in Hedgehog.Internal.Property

Semigroup a => Semigroup ( Label a) Source #

This semigroup is right biased. The name, location and percentage from the rightmost Label 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

newtype LabelName Source #

The name of a classifier.

Should be constructed using OverloadedStrings :

  "apples" :: LabelName

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.

newtype CoverCount Source #

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

Can be constructed using numeric literals:

  30 :: CoverCount

Constructors

CoverCount

Instances

Instances details
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

Instances

Instances details
Eq CoverPercentage Source #
Instance details

Defined in Hedgehog.Internal.Property

Fractional CoverPercentage Source #
Instance details

Defined in Hedgehog.Internal.Property

Num CoverPercentage Source #
Instance details

Defined in Hedgehog.Internal.Property

Ord CoverPercentage Source #
Instance details

Defined in Hedgehog.Internal.Property

Show CoverPercentage Source #
Instance details

Defined in Hedgehog.Internal.Property

Confidence

newtype Confidence Source #

The acceptable occurrence of false positives

Example, Confidence 10^9 would mean that you'd accept a false positive for 1 in 10^9 tests.

confidenceSuccess :: TestCount -> Confidence -> Coverage CoverCount -> Bool Source #

Is true when the test coverage satisfies the specified Confidence contstraint for all 'Coverage CoverCount's

confidenceFailure :: TestCount -> Confidence -> Coverage CoverCount -> Bool Source #

Is true when there exists a label that is sure to have failed according to the Confidence constraint

withConfidence :: Confidence -> Property -> Property Source #

Make sure that the result is statistically significant in accordance to the passed Confidence

defaultConfidence :: Confidence Source #

The default confidence allows one false positive in 10^9 tests

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.