Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module allows you to easily integrate the Hedgehog library with Test.Hspec test-suites.
To get started, check out the hedgehog
function, which lets you embed
a PropertyT
directly.
spec ::Spec
spec =describe
"my great test"$
doit
"generates stuff"$
hedgehog
$
do a <-forAll
generator a===
expected
Truth be told, the functionality is in the two orphan instances of
Example
for PropertyT
. You can directly use code in the
type. However, because most Hedgehog functions are abstract in
PropertyT
IO
MonadTest
, you might get errors about ambiguous types. The hedgehog
function fixes the type to
, which works out just
fine.PropertyT
IO
()
You can use all of hspec
's hooks with this, of course.
spec :: Spec spec =before
(pure
"Hello!")$
dodescribe
"with a string"$
doit
"gets a string"$
\ str ->hedgehog
$
do wrongLen <-forAll
$integral
(linear
0 3) length str/==
wrongLen
The function before
will make all the following spec items a function,
accepting that as a parameter. You should call hedgehog
after the
lambda.
If you are morally opposed to the pattern:
it
"message" $hedgehog
$ do True===
False
Then you can alternatively force the type some other way. One option is to use a no-op function, like this:
it
"message" $ dopure
() ::PropertyT
IO
() True===
False
This style has the advantage that parameters via hooks are less difficult to get right.
before
(pure
"Hello!") $ doit
"message" $ \str -> dopure
() ::PropertyT
IO
() wrongLen <-forAll
$integral
(linear
0 3)length
str/==
wrongLen
You don't have to remember to put the hedgehog
call after the lambda.
Synopsis
- hedgehog :: HasCallStack => PropertyT IO () -> PropertyT IO ()
- modifyArgs :: (Args -> Args) -> SpecWith a -> SpecWith a
- modifyMaxSuccess :: (Int -> Int) -> SpecWith a -> SpecWith a
- modifyMaxDiscardRatio :: (Int -> Int) -> SpecWith a -> SpecWith a
- modifyMaxShrinks :: (Int -> Int) -> SpecWith a -> SpecWith a
- module Hedgehog
The Main Function
hedgehog :: HasCallStack => PropertyT IO () -> PropertyT IO () Source #
Embed a Hedgehog
in an PropertyT
IO
()hspec
test.
spec ::Spec
spec =describe
"my great test"$
doit
"generates stuff"$
hedgehog
$
do a <-forAll
generator a===
expected
This function is only used to fix the type of the
monad
transformer. The functions in Hedgehog are typically abstract in
a PropertyT
MonadTest
, and it's easy to get ambiguous type errors if you leave
this out.
Since: 0.0.0.0
Hspec re-exports
modifyMaxSize
isn't re-exported, since
hedgehog has nothing that corresponds to it.
modifyMaxSuccess :: (Int -> Int) -> SpecWith a -> SpecWith a #
Use a modified maxSuccess
for given spec.
modifyMaxDiscardRatio :: (Int -> Int) -> SpecWith a -> SpecWith a #
Use a modified maxDiscardRatio
for given spec.
modifyMaxShrinks :: (Int -> Int) -> SpecWith a -> SpecWith a #
Use a modified maxShrinks
for given spec.
Hedgehog Re-exports
module Hedgehog
Orphan instances
m ~ IO => Example (PropertyT m ()) Source # | Warning: Orphan instance! This instance is used to embed a Hedgehog
property seamlessly into the Since: 0.0.0.0 |
evaluateExample :: PropertyT m () -> Params -> (ActionWith (Arg (PropertyT m ())) -> IO ()) -> ProgressCallback -> IO Result # | |
m ~ IO => Example (a -> PropertyT m ()) Source # | Warning: orphan instance! This instance is used to embed a Hedgehog
property seamlessly into the The instance will pick things up from the Test.Hspec.QuickCheck configuration. For example, if the program is supposed to use a predetermined seed, then the same seed will be used for QuickCheck and Hedgehog tests. Since: 0.0.0.0 |
evaluateExample :: (a -> PropertyT m ()) -> Params -> (ActionWith (Arg (a -> PropertyT m ())) -> IO ()) -> ProgressCallback -> IO Result # |