| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Test.Tasty.Hedgehog
Description
This package lets you test Hedgehog properties with tasty.
Typical usage would look like this:
testGroup "tasty-hedgehog tests" [ testProperty "reverse involutive" prop_reverse_involutive , testProperty "sort idempotent" prop_sort_idempotent ]
Synopsis
- testProperty :: TestName -> Property -> TestTree
- fromGroup :: Group -> TestTree
- newtype HedgehogReplay = HedgehogReplay (Maybe (Size, Seed))
- newtype HedgehogShowReplay = HedgehogShowReplay Bool
- newtype HedgehogTestLimit = HedgehogTestLimit (Maybe TestLimit)
- newtype HedgehogDiscardLimit = HedgehogDiscardLimit (Maybe DiscardLimit)
- newtype HedgehogShrinkLimit = HedgehogShrinkLimit (Maybe ShrinkLimit)
- newtype HedgehogShrinkRetries = HedgehogShrinkRetries (Maybe ShrinkRetries)
Documentation
Options you can pass in via tasty
newtype HedgehogReplay Source #
The replay token to use for replaying a previous test run
Constructors
| HedgehogReplay (Maybe (Size, Seed)) | 
Instances
| IsOption HedgehogReplay Source # | |
| Defined in Test.Tasty.Hedgehog | |
newtype HedgehogShowReplay Source #
If a test case fails, show a replay token for replaying tests
Constructors
| HedgehogShowReplay Bool | 
Instances
| IsOption HedgehogShowReplay Source # | |
| Defined in Test.Tasty.Hedgehog | |
newtype HedgehogTestLimit Source #
The number of successful test cases required before Hedgehog will pass a test
Constructors
| HedgehogTestLimit (Maybe TestLimit) | 
Instances
| Eq HedgehogTestLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods (==) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # (/=) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # | |
| Ord HedgehogTestLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods compare :: HedgehogTestLimit -> HedgehogTestLimit -> Ordering # (<) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # (<=) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # (>) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # (>=) :: HedgehogTestLimit -> HedgehogTestLimit -> Bool # max :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit # min :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit # | |
| Show HedgehogTestLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods showsPrec :: Int -> HedgehogTestLimit -> ShowS # show :: HedgehogTestLimit -> String # showList :: [HedgehogTestLimit] -> ShowS # | |
| IsOption HedgehogTestLimit Source # | |
| Defined in Test.Tasty.Hedgehog | |
newtype HedgehogDiscardLimit Source #
The number of discarded cases allowed before Hedgehog will fail a test
Constructors
| HedgehogDiscardLimit (Maybe DiscardLimit) | 
Instances
newtype HedgehogShrinkLimit Source #
The number of shrinks allowed before Hedgehog will fail a test
Constructors
| HedgehogShrinkLimit (Maybe ShrinkLimit) | 
Instances
| Eq HedgehogShrinkLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods (==) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # (/=) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # | |
| Ord HedgehogShrinkLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods compare :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Ordering # (<) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # (<=) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # (>) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # (>=) :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool # max :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit # min :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit # | |
| Show HedgehogShrinkLimit Source # | |
| Defined in Test.Tasty.Hedgehog Methods showsPrec :: Int -> HedgehogShrinkLimit -> ShowS # show :: HedgehogShrinkLimit -> String # showList :: [HedgehogShrinkLimit] -> ShowS # | |
| IsOption HedgehogShrinkLimit Source # | |
| Defined in Test.Tasty.Hedgehog | |
newtype HedgehogShrinkRetries Source #
The number of times to re-run a test during shrinking
Constructors
| HedgehogShrinkRetries (Maybe ShrinkRetries) |