Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
-
data
Property
=
Property
{
- propertyConfig :: ! PropertyConfig
- propertyTest :: PropertyT IO ()
-
newtype
PropertyT
m a =
PropertyT
{
- unPropertyT :: TestT ( GenT m) a
- newtype PropertyName = PropertyName { }
- data PropertyConfig = PropertyConfig { }
- newtype TestLimit = TestLimit Int
- newtype TestCount = TestCount Int
- newtype DiscardLimit = DiscardLimit Int
- newtype DiscardCount = DiscardCount Int
- newtype ShrinkLimit = ShrinkLimit Int
- newtype ShrinkCount = ShrinkCount Int
- data Skip
- newtype ShrinkPath = ShrinkPath [ Int ]
- newtype ShrinkRetries = ShrinkRetries Int
- withTests :: TestLimit -> Property -> Property
- withDiscards :: DiscardLimit -> Property -> Property
- withShrinks :: ShrinkLimit -> Property -> Property
- withRetries :: ShrinkRetries -> Property -> Property
- withSkip :: Skip -> Property -> Property
- property :: HasCallStack => PropertyT IO () -> Property
- test :: Monad m => TestT m a -> PropertyT m a
- forAll :: ( Monad m, Show a, HasCallStack ) => Gen a -> PropertyT m a
- forAllT :: ( Monad m, Show a, HasCallStack ) => GenT m a -> PropertyT m a
- forAllWith :: ( Monad m, HasCallStack ) => (a -> String ) -> Gen a -> PropertyT m a
- forAllWithT :: ( Monad m, HasCallStack ) => (a -> String ) -> GenT m a -> PropertyT m a
- defaultMinTests :: TestLimit
- discard :: Monad m => PropertyT m a
- skipCompress :: Skip -> String
- shrinkPathCompress :: ShrinkPath -> String
- skipDecompress :: String -> Maybe Skip
- shrinkPathDecompress :: String -> Maybe ShrinkPath
-
data
Group
=
Group
{
- groupName :: ! GroupName
- groupProperties :: ![( PropertyName , Property )]
- newtype GroupName = GroupName { }
- newtype PropertyCount = PropertyCount Int
- class Monad m => MonadTest m where
- type Test = TestT Identity
- newtype TestT m a = TestT { }
- data Log
-
newtype
Journal
=
Journal
{
- journalLogs :: [ Log ]
- data Failure = Failure ( Maybe Span ) String ( Maybe Diff )
-
data
Diff
=
Diff
{
- diffPrefix :: String
- diffRemoved :: String
- diffInfix :: String
- diffAdded :: String
- diffSuffix :: String
- diffValue :: ValueDiff
- annotate :: ( MonadTest m, HasCallStack ) => String -> m ()
- annotateShow :: ( MonadTest m, Show a, HasCallStack ) => a -> m ()
- footnote :: MonadTest m => String -> m ()
- footnoteShow :: ( MonadTest m, Show a) => a -> m ()
- failure :: ( MonadTest m, HasCallStack ) => m a
- success :: MonadTest m => m ()
- assert :: ( MonadTest m, HasCallStack ) => Bool -> m ()
- diff :: ( MonadTest m, Show a, Show b, HasCallStack ) => a -> (a -> b -> Bool ) -> b -> m ()
- (===) :: ( MonadTest m, Eq a, Show a, HasCallStack ) => a -> a -> m ()
- (/==) :: ( MonadTest m, Eq a, Show a, HasCallStack ) => a -> a -> m ()
- eval :: ( MonadTest m, HasCallStack ) => a -> m a
- evalNF :: ( MonadTest m, NFData a, HasCallStack ) => a -> m a
- evalM :: ( MonadTest m, MonadCatch m, HasCallStack ) => m a -> m a
- evalIO :: ( MonadTest m, MonadIO m, HasCallStack ) => IO a -> m a
- evalEither :: ( MonadTest m, Show x, HasCallStack ) => Either x a -> m a
- evalEitherM :: ( MonadTest m, Show x, MonadCatch m, HasCallStack ) => m ( Either x a) -> m a
- evalExceptT :: ( MonadTest m, Show x, HasCallStack ) => ExceptT x m a -> m a
- evalMaybe :: ( MonadTest m, Show a, HasCallStack ) => Maybe a -> m a
- evalMaybeM :: ( MonadTest m, Show a, MonadCatch m, HasCallStack ) => m ( Maybe a) -> m a
-
newtype
Coverage
a =
Coverage
{
- coverageLabels :: Map LabelName ( Label a)
-
data
Label
a =
MkLabel
{
- labelName :: ! LabelName
- labelLocation :: !( Maybe Span )
- labelMinimum :: ! CoverPercentage
- labelAnnotation :: !a
- newtype LabelName = LabelName { }
- cover :: ( MonadTest m, HasCallStack ) => CoverPercentage -> LabelName -> Bool -> m ()
- classify :: ( MonadTest m, HasCallStack ) => LabelName -> Bool -> m ()
- label :: ( MonadTest m, HasCallStack ) => LabelName -> m ()
- collect :: ( MonadTest m, Show a, HasCallStack ) => a -> m ()
- coverPercentage :: TestCount -> CoverCount -> CoverPercentage
- labelCovered :: TestCount -> Label CoverCount -> Bool
- coverageSuccess :: TestCount -> Coverage CoverCount -> Bool
- coverageFailures :: TestCount -> Coverage CoverCount -> [ Label CoverCount ]
- journalCoverage :: Journal -> Coverage CoverCount
- data Cover
-
newtype
CoverCount
=
CoverCount
{
- unCoverCount :: Int
- newtype CoverPercentage = CoverPercentage { }
- toCoverCount :: Cover -> CoverCount
- newtype Confidence = Confidence { }
- data TerminationCriteria
- confidenceSuccess :: TestCount -> Confidence -> Coverage CoverCount -> Bool
- confidenceFailure :: TestCount -> Confidence -> Coverage CoverCount -> Bool
- withConfidence :: Confidence -> Property -> Property
- verifiedTermination :: Property -> Property
- defaultConfidence :: Confidence
- defaultConfig :: PropertyConfig
- mapConfig :: ( PropertyConfig -> PropertyConfig ) -> Property -> Property
- failDiff :: ( MonadTest m, Show a, Show b, HasCallStack ) => a -> b -> m ()
- failException :: ( MonadTest m, HasCallStack ) => SomeException -> m a
- failWith :: ( MonadTest m, HasCallStack ) => Maybe Diff -> String -> m a
- writeLog :: MonadTest m => Log -> m ()
- mkTest :: ( Either Failure a, Journal ) -> Test a
- mkTestT :: m ( Either Failure a, Journal ) -> TestT m a
- runTest :: Test a -> ( Either Failure a, Journal )
- runTestT :: TestT m a -> m ( Either Failure a, Journal )
- wilsonBounds :: Integer -> Integer -> Double -> ( Double , Double )
Property
A property test, along with some configurable limits like how many times to run the test.
Property | |
|
newtype PropertyT m a Source #
The property monad transformer allows both the generation of test inputs and the assertion of expectations.
PropertyT | |
|
Instances
newtype PropertyName Source #
The name of a property.
Should be constructed using
OverloadedStrings
:
"apples" :: PropertyName
Instances
data PropertyConfig Source #
Configuration for a property test.
PropertyConfig | |
|
Instances
Eq PropertyConfig Source # | |
Defined in Hedgehog.Internal.Property (==) :: PropertyConfig -> PropertyConfig -> Bool Source # (/=) :: PropertyConfig -> PropertyConfig -> Bool Source # |
|
Ord PropertyConfig Source # | |
Defined in Hedgehog.Internal.Property compare :: PropertyConfig -> PropertyConfig -> Ordering Source # (<) :: PropertyConfig -> PropertyConfig -> Bool Source # (<=) :: PropertyConfig -> PropertyConfig -> Bool Source # (>) :: PropertyConfig -> PropertyConfig -> Bool Source # (>=) :: PropertyConfig -> PropertyConfig -> Bool Source # max :: PropertyConfig -> PropertyConfig -> PropertyConfig Source # min :: PropertyConfig -> PropertyConfig -> PropertyConfig Source # |
|
Show PropertyConfig Source # | |
Defined in Hedgehog.Internal.Property |
|
Lift PropertyConfig Source # | |
Defined in Hedgehog.Internal.Property lift :: PropertyConfig -> Q Exp Source # liftTyped :: PropertyConfig -> Q ( TExp PropertyConfig ) 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
Instances
The number of tests a property ran successfully.
Instances
newtype DiscardLimit Source #
The number of discards to allow before giving up.
Can be constructed using numeric literals:
10000 :: DiscardLimit
Instances
newtype DiscardCount Source #
The number of tests a property had to discard.
Instances
newtype ShrinkLimit Source #
The number of shrinks to try before giving up on shrinking.
Can be constructed using numeric literals:
1000 :: ShrinkLimit
Instances
newtype ShrinkCount Source #
The numbers of times a property was able to shrink after a failing test.
Instances
Where to start running a property's tests.
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. |
Instances
Eq Skip Source # | |
Ord Skip Source # | |
Defined in Hedgehog.Internal.Property |
|
Show Skip Source # | |
IsString Skip Source # |
We use this instance to support usage like withSkip "3:aB"
It throws an error if the input is not a valid compressed
|
Defined in Hedgehog.Internal.Property fromString :: String -> Skip Source # |
|
Lift Skip Source # | |
newtype ShrinkPath Source #
The path taken to reach a shrink state.
ShrinkPath [ Int ] |
Instances
Eq ShrinkPath Source # | |
Defined in Hedgehog.Internal.Property (==) :: ShrinkPath -> ShrinkPath -> Bool Source # (/=) :: ShrinkPath -> ShrinkPath -> Bool Source # |
|
Ord ShrinkPath Source # | |
Defined in Hedgehog.Internal.Property compare :: ShrinkPath -> ShrinkPath -> Ordering Source # (<) :: ShrinkPath -> ShrinkPath -> Bool Source # (<=) :: ShrinkPath -> ShrinkPath -> Bool Source # (>) :: ShrinkPath -> ShrinkPath -> Bool Source # (>=) :: ShrinkPath -> ShrinkPath -> Bool Source # max :: ShrinkPath -> ShrinkPath -> ShrinkPath Source # min :: ShrinkPath -> ShrinkPath -> ShrinkPath Source # |
|
Show ShrinkPath Source # | |
Defined in Hedgehog.Internal.Property |
|
Lift ShrinkPath Source # | |
Defined in Hedgehog.Internal.Property lift :: ShrinkPath -> Q Exp Source # liftTyped :: ShrinkPath -> Q ( TExp ShrinkPath ) Source # |
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
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 #
forAllWithT :: ( Monad m, HasCallStack ) => (a -> String ) -> GenT m a -> PropertyT m a Source #
defaultMinTests :: TestLimit Source #
The minimum amount of tests to run for a
Property
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.
Group
A named collection of property tests.
Group | |
|
The name of a group of properties.
Should be constructed using
OverloadedStrings
:
"fruit" :: GroupName
Instances
Eq GroupName Source # | |
Ord GroupName Source # | |
Defined in Hedgehog.Internal.Property |
|
Show GroupName Source # | |
IsString GroupName Source # | |
Defined in Hedgehog.Internal.Property fromString :: String -> GroupName Source # |
|
Semigroup GroupName Source # | |
Lift GroupName Source # | |
newtype PropertyCount Source #
The number of properties in a group.
Instances
TestT
class Monad m => MonadTest m where Source #
Instances
MonadTest m => MonadTest ( MaybeT m) Source # | |
MonadTest m => MonadTest ( ResourceT m) Source # | |
Monad m => MonadTest ( TestT m) Source # | |
Monad m => MonadTest ( PropertyT m) Source # | |
MonadTest m => MonadTest ( ReaderT r m) Source # | |
MonadTest m => MonadTest ( ExceptT x m) Source # | |
( MonadTest m, Monoid w) => MonadTest ( WriterT w m) Source # | |
MonadTest m => MonadTest ( StateT s m) Source # | |
MonadTest m => MonadTest ( IdentityT m) Source # | |
MonadTest m => MonadTest ( StateT s m) Source # | |
( MonadTest m, Monoid w) => MonadTest ( WriterT w m) Source # | |
MonadTest m => MonadTest ( ContT r m) Source # | |
( MonadTest m, Monoid w) => MonadTest ( RWST r w s m) Source # | |
( MonadTest m, Monoid w) => MonadTest ( RWST r w s m) Source # | |
A test monad transformer allows the assertion of expectations.
Instances
Log messages which are recorded during a test run.
Instances
A record containing the details of a test run.
Journal | |
|
The difference between some expected and actual value.
Diff | |
|
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.
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.
evalEither :: ( MonadTest m, Show x, HasCallStack ) => Either x a -> m a Source #
evalEitherM :: ( MonadTest m, Show x, MonadCatch m, HasCallStack ) => m ( Either x a) -> m a Source #
evalExceptT :: ( MonadTest m, Show x, HasCallStack ) => ExceptT x m a -> m a Source #
evalMaybeM :: ( MonadTest m, Show a, MonadCatch m, HasCallStack ) => m ( Maybe a) -> m a Source #
Coverage
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.
Coverage | |
|
Instances
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.
MkLabel | |
|
Instances
Functor Label Source # | |
Foldable Label Source # | |
Defined in Hedgehog.Internal.Property fold :: Monoid m => Label m -> m Source # foldMap :: Monoid m => (a -> m) -> Label a -> m Source # foldMap' :: Monoid m => (a -> m) -> Label a -> m Source # foldr :: (a -> b -> b) -> b -> Label a -> b Source # foldr' :: (a -> b -> b) -> b -> Label a -> b Source # foldl :: (b -> a -> b) -> b -> Label a -> b Source # foldl' :: (b -> a -> b) -> b -> Label a -> b Source # foldr1 :: (a -> a -> a) -> Label a -> a Source # foldl1 :: (a -> a -> a) -> Label a -> a Source # toList :: Label a -> [a] Source # null :: Label a -> Bool Source # length :: Label a -> Int Source # elem :: Eq a => a -> Label a -> Bool Source # maximum :: Ord a => Label a -> a Source # minimum :: Ord a => Label a -> a Source # |
|
Traversable Label Source # | |
Defined in Hedgehog.Internal.Property |
|
Eq a => Eq ( Label a) Source # | |
Show a => Show ( Label a) Source # | |
Semigroup a => Semigroup ( Label a) Source # |
This semigroup is right biased. The name, location and percentage from the
rightmost
|
The name of a classifier.
Should be constructed using
OverloadedStrings
:
"apples" :: LabelName
Instances
Eq LabelName Source # | |
Ord LabelName Source # | |
Defined in Hedgehog.Internal.Property |
|
Show LabelName Source # | |
IsString LabelName Source # | |
Defined in Hedgehog.Internal.Property fromString :: String -> LabelName Source # |
|
Semigroup LabelName Source # | |
Monoid LabelName Source # | |
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.
coverPercentage :: TestCount -> CoverCount -> CoverPercentage Source #
labelCovered :: TestCount -> Label CoverCount -> Bool Source #
coverageSuccess :: TestCount -> Coverage CoverCount -> Bool Source #
All labels are covered
coverageFailures :: TestCount -> Coverage CoverCount -> [ Label CoverCount ] Source #
Whether a test is covered by a classifier, and therefore belongs to a
Class
.
newtype CoverCount Source #
The total number of tests which are covered by a classifier.
Can be constructed using numeric literals:
30 :: CoverCount
Instances
newtype CoverPercentage Source #
The relative number of tests which are covered by a classifier.
Can be constructed using numeric literals:
30 :: CoverPercentage
Instances
toCoverCount :: Cover -> CoverCount Source #
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.
Instances
data TerminationCriteria Source #
EarlyTermination Confidence TestLimit | |
NoEarlyTermination Confidence TestLimit | |
NoConfidenceTermination TestLimit |
Instances
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.