| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Test.Tasty.Hedgehog.Coverage
Description
Provide some functionality for tracking the distribution of test inputs when using Hedgehog property-based testing.
Synopsis
- data Cover = Cover {
- _coverageConf :: !PropertyConfig
 - _coverageProp :: PropertyT (StateT Tally IO) ()
 
 - newtype Tally = Tally {}
 - testPropertyCoverage :: TestName -> Cover -> TestTree
 - withCoverage :: HasCallStack => PropertyT (StateT Tally IO) () -> Cover
 - classify :: MonadState Tally m => Bool -> Text -> m ()
 - label :: MonadState Tally m => Text -> m ()
 - collect :: (MonadState Tally m, Show a) => a -> m ()
 - withTests :: TestLimit -> Cover -> Cover
 - withRetries :: ShrinkRetries -> Cover -> Cover
 - withDiscards :: DiscardLimit -> Cover -> Cover
 - withShrinks :: ShrinkLimit -> Cover -> Cover
 
Data types
Equivalent to the Property type from Hedgehog, but slightly modified for
 the purpose of enabling the classification functionality.
Constructors
| Cover | |
Fields 
  | |
This is the type used to store the information about the inputs.
Test helpers
withCoverage :: HasCallStack => PropertyT (StateT Tally IO) () -> Cover Source #
Coverage functions
Arguments
| :: MonadState Tally m | |
| => Bool | 
  | 
| -> Text | The label for this input.  | 
| -> m () | 
Records how many test cases satisfy a given condition.
prop_reverse_involutive :: Cover prop_reverse_involutive = withCoverage $ do xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha classify (length xs > 50) "non-trivial" test_involutive reverse xs
Which gives output similar to:
reverse involutive: OK 18.00% non-trivial
Arguments
| :: MonadState Tally m | |
| => Text | The label for the input.  | 
| -> m () | 
Attach a simple label to a property.
prop_reverse_reverse :: Cover
prop_reverse_reverse = withCoverage $ do
  xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha
  label ("length of input is " ++ show (length xs))
  reverse (reverse xs) === xs
Which gives output similar to:
reverse involutive:          OK
    4.00% with a length of 0
    7.00% with a length of 1
    3.00% with a length of 11
    2.00% with a length of 12
    2.00% with a length of 13
    ...
Arguments
| :: (MonadState Tally m, Show a) | |
| => a | The input to collect.  | 
| -> m () | 
Uses the input itself as the label, useful for recording test case distribution.
prop_reverse_reverse :: Cover prop_reverse_reverse = withCoverage $ do xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha collect (length xs) reverse (reverse xs) === xs
Which gives output similar to:
reverse involutive:          OK
    8.00% ""
    1.00% "AFkNJBLiWYEBFRyZhulpMkkqIvsDpLAmaYoFTnNNFfkrbPUqDIRUuZOFGohTfB"
    1.00% "AWWfLCfmZPoydVYXwnFHyCEWztXanEzdoc"
    1.00% "CJJVBGOeaIkLfcOUGV"
    1.00% "CNrTsblqfEz"
    1.00% "CxDqm"
Property Config Helpers
These functions work exactly as their original Hedgehog counterparts, only modified to work with the Cover type.
withTests :: TestLimit -> Cover -> Cover 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.
withRetries :: ShrinkRetries -> Cover -> Cover 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.
withDiscards :: DiscardLimit -> Cover -> Cover Source #
Set the number of times a property is allowed to discard before the test runner gives up.
withShrinks :: ShrinkLimit -> Cover -> Cover Source #
Set the number of times a property is allowed to shrink before the test runner gives up and prints the counterexample.