Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module includes almost everything you need to get started writing property tests with Hedgehog.
It is designed to be used alongside Hedgehog.Gen and Hedgehog.Range , which should be imported qualified. You also need to enable Template Haskell so the Hedgehog test runner can find your properties.
{-# LANGUAGE TemplateHaskell #-} import Hedgehog import qualified Hedgehog.Gen as Gen import qualified Hedgehog.Range as Range
Once you have your imports set up, you can write a simple property:
prop_reverse :: Property prop_reverse = property $ do xs <- forAll $ Gen.list (Range.linear 0 100) Gen.alpha reverse (reverse xs) === xs
And add the Template Haskell splice which will discover your properties:
tests :: IO Bool tests = checkParallel $$(discover)
If you prefer to avoid macros, you can specify the group of properties to run manually instead:
{-# LANGUAGE OverloadedStrings #-} tests :: IO Bool tests = checkParallel $ Group "Test.Example" [ ("prop_reverse", prop_reverse) ]
You can then load the module in GHCi, and run it:
λ tests ━━━ Test.Example ━━━ ✓ prop_reverse passed 100 tests.
Synopsis
- data Property
- data PropertyT m a
-
data
Group
=
Group
{
- groupName :: ! GroupName
- groupProperties :: ![( PropertyName , Property )]
- data PropertyName
- data GroupName
- 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
- forAllWith :: ( Monad m, HasCallStack ) => (a -> String ) -> Gen a -> PropertyT m a
- discard :: Monad m => PropertyT m a
- check :: MonadIO m => Property -> m Bool
- recheck :: MonadIO m => Size -> Seed -> Property -> m ()
- recheckAt :: MonadIO m => Seed -> Skip -> Property -> m ()
- discover :: TExpQ Group
- discoverPrefix :: String -> TExpQ Group
- checkParallel :: MonadIO m => Group -> m Bool
- checkSequential :: MonadIO m => Group -> m Bool
- data Confidence
- verifiedTermination :: Property -> Property
- withConfidence :: Confidence -> Property -> Property
- withTests :: TestLimit -> Property -> Property
- data TestLimit
- withDiscards :: DiscardLimit -> Property -> Property
- data DiscardLimit
- withShrinks :: ShrinkLimit -> Property -> Property
- data ShrinkLimit
- withRetries :: ShrinkRetries -> Property -> Property
- data ShrinkRetries
- withSkip :: Skip -> Property -> Property
- data Skip
- type Gen = GenT Identity
- data GenT m a
- class ( Monad m, Monad ( GenBase m)) => MonadGen m where
- data Range a
- newtype Size = Size { }
- data Seed = Seed { }
- type Test = TestT Identity
- data TestT m a
- class Monad m => MonadTest m where
- 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 ()
- success :: MonadTest m => m ()
- failure :: ( MonadTest m, HasCallStack ) => m a
- 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 ()
- tripping :: ( MonadTest m, Applicative f, Show b, Show (f a), Eq (f a), HasCallStack ) => a -> (a -> b) -> (b -> f 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
- data LabelName
- classify :: ( MonadTest m, HasCallStack ) => LabelName -> Bool -> m ()
- cover :: ( MonadTest m, HasCallStack ) => CoverPercentage -> LabelName -> Bool -> m ()
- label :: ( MonadTest m, HasCallStack ) => LabelName -> m ()
- collect :: ( MonadTest m, Show a, HasCallStack ) => a -> m ()
-
data
Command
gen m (state :: (
Type
->
Type
) ->
Type
) =
forall
input output.(
TraversableB
input,
Show
(input
Symbolic
),
Show
output,
Typeable
output) =>
Command
{
- commandGen :: state Symbolic -> Maybe (gen (input Symbolic ))
- commandExecute :: input Concrete -> m output
- commandCallbacks :: [ Callback input output state]
- data Callback input output state
- data Action m (state :: ( Type -> Type ) -> Type )
-
newtype
Sequential
m state =
Sequential
{
- sequentialActions :: [ Action m state]
-
data
Parallel
m state =
Parallel
{
- parallelPrefix :: [ Action m state]
- parallelBranch1 :: [ Action m state]
- parallelBranch2 :: [ Action m state]
- executeSequential :: ( MonadTest m, MonadCatch m, HasCallStack ) => ( forall v. state v) -> Sequential m state -> m ()
- executeParallel :: ( MonadTest m, MonadCatch m, MonadBaseControl IO m, HasCallStack ) => ( forall v. state v) -> Parallel m state -> m ()
- newtype Var a v = Var (v a)
- concrete :: Var a Concrete -> a
- opaque :: Var ( Opaque a) Concrete -> a
- data Symbolic a
- newtype Concrete a where
-
newtype
Opaque
a =
Opaque
{
- unOpaque :: a
- distributeT :: ( MonadTransDistributive g, Transformer f g m) => g (f m) a -> f (g m) a
-
class
FunctorB
(b :: (k ->
Type
) ->
Type
)
where
- bmap :: ( forall (a :: k). f a -> g a) -> b f -> b g
-
class
FunctorB
b =>
TraversableB
(b :: (k ->
Type
) ->
Type
)
where
- btraverse :: Applicative e => ( forall (a :: k). f a -> e (g a)) -> b f -> e (b g)
- newtype Rec p a (x :: k) = Rec { }
- class Eq1 (f :: Type -> Type )
- eq1 :: ( Eq1 f, Eq a) => f a -> f a -> Bool
- class Eq1 f => Ord1 (f :: Type -> Type )
- compare1 :: ( Ord1 f, Ord a) => f a -> f a -> Ordering
- class Show1 (f :: Type -> Type )
- showsPrec1 :: ( Show1 f, Show a) => Int -> f a -> ShowS
-
class
HTraversable
t
where
- htraverse :: Applicative f => ( forall a. g a -> f (h a)) -> t g -> f (t h)
Properties
A property test, along with some configurable limits like how many times to run the test.
The property monad transformer allows both the generation of test inputs and the assertion of expectations.
Instances
A named collection of property tests.
Group | |
|
data PropertyName Source #
The name of a property.
Should be constructed using
OverloadedStrings
:
"apples" :: PropertyName
Instances
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 # | |
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.
forAllWith :: ( Monad m, HasCallStack ) => (a -> String ) -> Gen a -> PropertyT m a Source #
recheck :: MonadIO m => Size -> Seed -> Property -> m () Source #
Check a property using a specific size and seed.
discover :: TExpQ Group Source #
Discover all the properties in a module.
Functions starting with
prop_
are assumed to be properties.
checkParallel :: MonadIO m => Group -> m Bool Source #
Check a group of properties in parallel.
Warning: although this check function runs tests faster than
checkSequential
, it should be noted that it may cause problems with
properties that are not self-contained. For example, if you have a group
of tests which all use the same database table, you may find that they
interfere with each other when being run in parallel.
Using Template Haskell for property discovery:
tests :: IO Bool tests = checkParallel $$(discover)
With manually specified properties:
tests :: IO Bool tests = checkParallel $ Group "Test.Example" [ ("prop_reverse", prop_reverse) ]
checkSequential :: MonadIO m => Group -> m Bool Source #
Check a group of properties sequentially.
Using Template Haskell for property discovery:
tests :: IO Bool tests = checkSequential $$(discover)
With manually specified properties:
tests :: IO Bool tests = checkSequential $ Group "Test.Example" [ ("prop_reverse", prop_reverse) ]
data 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
withConfidence :: Confidence -> Property -> Property Source #
Make sure that the result is statistically significant in accordance to
the passed
Confidence
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.
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
withDiscards :: DiscardLimit -> Property -> Property Source #
Set the number of times a property is allowed to discard before the test runner gives up.
data DiscardLimit Source #
The number of discards to allow before giving up.
Can be constructed using numeric literals:
10000 :: DiscardLimit
Instances
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.
data ShrinkLimit Source #
The number of shrinks to try before giving up on shrinking.
Can be constructed using numeric literals:
1000 :: ShrinkLimit
Instances
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.
data 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
withSkip :: Skip -> Property -> Property Source #
Set the target that a property will skip to before it starts to run.
Where to start running a property's tests.
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 # | |
Generating Test Data
Monad transformer which can generate random values of
a
.
Instances
class ( Monad m, Monad ( GenBase m)) => MonadGen m where Source #
Class of monads which can generate input data for tests.
Instances
MonadGen m => MonadGen ( MaybeT m) Source # | |
Monad m => MonadGen ( GenT m) Source # | |
MonadGen m => MonadGen ( ReaderT r m) Source # | |
MonadGen m => MonadGen ( ExceptT x m) Source # | |
( MonadGen m, Monoid w) => MonadGen ( WriterT w m) Source # | |
MonadGen m => MonadGen ( StateT r m) Source # | |
MonadGen m => MonadGen ( IdentityT m) Source # | |
MonadGen m => MonadGen ( StateT r m) Source # | |
( MonadGen m, Monoid w) => MonadGen ( WriterT w m) Source # | |
Tests are parameterized by the size of the randomly-generated data. The
meaning of a
Size
value depends on the particular generator used, but
it must always be a number between 0 and 99 inclusive.
Instances
Enum Size Source # | |
Eq Size Source # | |
Integral Size Source # | |
Defined in Hedgehog.Internal.Range |
|
Num Size Source # | |
Ord Size Source # | |
Defined in Hedgehog.Internal.Range |
|
Read Size Source # | |
Real Size Source # | |
Defined in Hedgehog.Internal.Range toRational :: Size -> Rational Source # |
|
Show Size Source # | |
A splittable random number generator.
Instances
Eq Seed Source # | |
Ord Seed Source # | |
Defined in Hedgehog.Internal.Seed |
|
Read Seed Source # | |
Show Seed Source # | |
RandomGen Seed Source # | |
Defined in Hedgehog.Internal.Seed next :: Seed -> ( Int , Seed ) Source # genWord8 :: Seed -> ( Word8 , Seed ) Source # genWord16 :: Seed -> ( Word16 , Seed ) Source # genWord32 :: Seed -> ( Word32 , Seed ) Source # genWord64 :: Seed -> ( Word64 , Seed ) Source # genWord32R :: Word32 -> Seed -> ( Word32 , Seed ) Source # genWord64R :: Word64 -> Seed -> ( Word64 , Seed ) Source # genShortByteString :: Int -> Seed -> ( ShortByteString , Seed ) Source # |
|
Lift Seed Source # | |
Tests
A test monad transformer allows the assertion of expectations.
Instances
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 # | |
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.
tripping :: ( MonadTest m, Applicative f, Show b, Show (f a), Eq (f a), HasCallStack ) => a -> (a -> b) -> (b -> f a) -> m () Source #
Test that a pair of encode / decode functions are compatible.
Given a printer from some type
a -> b
, and a parser with a
potential failure case
b -> f a
. Ensure that a valid
a
round
trips through the "print" and "parse" to yield the same
a
.
For example, types
should
have tripping
Read
and
Show
instances:
trippingShowRead :: (Show a, Read a, Eq a, MonadTest m) => a -> m () trippingShowRead a = tripping a show readEither
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 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 # | |
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
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.
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.
State Machine Tests
data Command gen m (state :: ( Type -> Type ) -> Type ) Source #
The specification for the expected behaviour of an
Action
. These are used to generate sequences of actions to test.
This is the main type you will use when writing state machine
tests.
gen
is usually an instance of
MonadGen
, and
m
is usually
an instance of
MonadTest
. These constraints appear when you pass
your
Command
list to
sequential
or
parallel
.
forall input output.( TraversableB input, Show (input Symbolic ), Show output, Typeable output) => Command | |
|
data Callback input output state Source #
Optional command configuration.
Require (state Symbolic -> input Symbolic -> Bool ) |
A pre-condition for a command that must be verified before the command can be executed. This is mainly used during shrinking to ensure that it is still OK to run a command despite the fact that some previously executed commands may have been removed from the sequence. |
Update ( forall v. Ord1 v => state v -> input v -> Var output v -> state v) |
Updates the model state, given the input and output of the command. Note
that this function is polymorphic in the type of values. This is because
it must work over
|
Ensure (state Concrete -> state Concrete -> input Concrete -> output -> Test ()) |
A post-condition for a command that must be verified for the command to be considered a success. This callback receives the state prior to execution as the first argument, and the state after execution as the second argument. |
data Action m (state :: ( Type -> Type ) -> Type ) Source #
An instantiation of a
Command
which can be executed, and its effect
evaluated.
newtype Sequential m state Source #
A sequence of actions to execute.
Sequential | |
|
Instances
Show ( Sequential m state) Source # | |
Defined in Hedgehog.Internal.State |
data Parallel m state Source #
A sequential prefix of actions to execute, with two branches to execute in parallel.
Parallel | |
|
executeSequential :: ( MonadTest m, MonadCatch m, HasCallStack ) => ( forall v. state v) -> Sequential m state -> m () Source #
Executes a list of actions sequentially, verifying that all post-conditions are met and no exceptions are thrown.
To generate a sequence of actions to execute, see the
sequential
combinator in the
Hedgehog.Gen
module.
executeParallel :: ( MonadTest m, MonadCatch m, MonadBaseControl IO m, HasCallStack ) => ( forall v. state v) -> Parallel m state -> m () Source #
Executes the prefix actions sequentially, then executes the two branches in parallel, verifying that no exceptions are thrown and that there is at least one sequential interleaving where all the post-conditions are met.
To generate parallel actions to execute, see the
parallel
combinator in the
Hedgehog.Gen
module.
Variables are the potential or actual result of executing an action. They
are parameterised by either
Symbolic
or
Concrete
depending on the
phase of the test.
Symbolic
variables are the potential results of actions. These are used
when generating the sequence of actions to execute. They allow actions
which occur later in the sequence to make use of the result of an action
which came earlier in the sequence.
Concrete
variables are the actual results of actions. These are used
during test execution. They provide access to the actual runtime value of
a variable.
The state update
Callback
for a command needs to be polymorphic in the
type of variable because it is used in both the generation and the
execution phase.
The order of arguments makes
Var
HTraverable
, which is how
Symbolic
values are turned into
Concrete
ones.
Var (v a) |
Instances
TraversableB ( Var a :: ( Type -> Type ) -> Type ) Source # | |
Defined in Hedgehog.Internal.State |
|
FunctorB ( Var a :: ( Type -> Type ) -> Type ) Source # | |
( Eq a, Eq1 v) => Eq ( Var a v) Source # | |
( Ord a, Ord1 v) => Ord ( Var a v) Source # | |
Defined in Hedgehog.Internal.State |
|
( Show a, Show1 v) => Show ( Var a v) Source # | |
Symbolic values: Because hedgehog generates actions in a separate phase before execution, you will sometimes need to refer to the result of a previous action in a generator without knowing the value of the result (e.g., to get the ID of a previously-created user).
Symbolic variables provide a token to stand in for the actual variables at
generation time (and in
Require
/
Update
callbacks). At execution time,
real values are available, so your execute actions work on
Concrete
variables.
Instances
Eq1 Symbolic Source # | |
Ord1 Symbolic Source # | |
Defined in Hedgehog.Internal.State |
|
Show1 Symbolic Source # | |
Eq ( Symbolic a) Source # | |
Ord ( Symbolic a) Source # | |
Defined in Hedgehog.Internal.State compare :: Symbolic a -> Symbolic a -> Ordering Source # (<) :: Symbolic a -> Symbolic a -> Bool Source # (<=) :: Symbolic a -> Symbolic a -> Bool Source # (>) :: Symbolic a -> Symbolic a -> Bool Source # (>=) :: Symbolic a -> Symbolic a -> Bool Source # |
|
Show ( Symbolic a) Source # | |
newtype Concrete a where Source #
Concrete values: At test-execution time,
Symbolic
values from generation
are replaced with
Concrete
values from performing actions. This type
gives us something of the same kind as
Symbolic
to pass as a type
argument to
Var
.
Instances
Opaque values.
Useful if you want to put something without a
Show
instance inside
something which you'd like to be able to display.
For example:
data State v = State { stateRefs :: [Var (Opaque (IORef Int)) v] } deriving (Eq, Show)
Instances
Eq a => Eq ( Opaque a) Source # | |
Ord a => Ord ( Opaque a) Source # | |
Defined in Hedgehog.Internal.Opaque |
|
Show ( Opaque a) Source # | |
Transformers
distributeT :: ( MonadTransDistributive g, Transformer f g m) => g (f m) a -> f (g m) a Source #
Distribute one monad transformer over another.
Functors
FunctorB
and
TraversableB
must be implemented for all
Command
input
types.
This is most easily achieved using
DeriveGeneric
:
data Register v = Register Name (Var Pid v) deriving (Eq, Show, Generic) instance FunctorB Register instance TraversableB Register newtype Unregister (v :: * -> *) = Unregister Name deriving (Eq, Show, Generic) instance FunctorB Unregister instance TraversableB Unregister
DeriveAnyClass
and
DerivingStrategies
allow a more compact syntax:
data Register v = Register Name (Var Pid v) deriving (Eq, Show, Generic, FunctorB, TraversableB) newtype Unregister (v :: * -> *) = Unregister Name deriving (Eq, Show, Generic) deriving anyclass (FunctorB, TraversableB)
class FunctorB (b :: (k -> Type ) -> Type ) where Source #
Barbie-types that can be mapped over. Instances of
FunctorB
should
satisfy the following laws:
bmap
id
=id
bmap
f .bmap
g =bmap
(f . g)
There is a default
bmap
implementation for
Generic
types, so
instances can derived automatically.
Nothing
Instances
FunctorB ( Proxy :: (k -> Type ) -> Type ) | |
FunctorB ( Constant x :: (k -> Type ) -> Type ) | |
FunctorB ( Const x :: (k -> Type ) -> Type ) | |
( FunctorB a, FunctorB b) => FunctorB ( Sum a b :: (k -> Type ) -> Type ) | |
( FunctorB a, FunctorB b) => FunctorB ( Product a b :: (k -> Type ) -> Type ) | |
( Functor f, FunctorB b) => FunctorB ( Compose f b :: (k -> Type ) -> Type ) | |
FunctorB ( Var a :: ( Type -> Type ) -> Type ) Source # | |
class FunctorB b => TraversableB (b :: (k -> Type ) -> Type ) where Source #
Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:
t .btraverse
f =btraverse
(t . f) -- naturalitybtraverse
Identity
=Identity
-- identitybtraverse
(Compose
.fmap
g . f) =Compose
.fmap
(btraverse
g) .btraverse
f -- composition
There is a default
btraverse
implementation for
Generic
types, so
instances can derived automatically.
Nothing
btraverse :: Applicative e => ( forall (a :: k). f a -> e (g a)) -> b f -> e (b g) Source #
Instances
TraversableB ( Proxy :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
TraversableB ( Constant a :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
TraversableB ( Const a :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
( TraversableB a, TraversableB b) => TraversableB ( Sum a b :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
( TraversableB a, TraversableB b) => TraversableB ( Product a b :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
( Traversable f, TraversableB b) => TraversableB ( Compose f b :: (k -> Type ) -> Type ) | |
Defined in Barbies.Internal.TraversableB |
|
TraversableB ( Var a :: ( Type -> Type ) -> Type ) Source # | |
Defined in Hedgehog.Internal.State |
newtype Rec p a (x :: k) Source #
Instances
GConstraints n (c :: k1 -> Constraint ) (f :: k2) ( Rec a' a :: Type -> Type ) ( Rec b' b :: k3 -> Type ) ( Rec b' b :: k3 -> Type ) | |
GConstraints n (c :: k1 -> Constraint ) (f :: k1 -> Type ) ( Rec (P n ( X :: k1 -> Type ) a') ( X a) :: Type -> Type ) ( Rec (P n f a') (f a) :: k2 -> Type ) ( Rec (P n ( Product ( Dict c) f) a') ( Product ( Dict c) f a) :: k2 -> Type ) | |
type GAll n (c :: k -> Constraint ) ( Rec l r :: Type -> Type ) | |
Defined in Barbies.Generics.Constraints |
class Eq1 (f :: Type -> Type ) Source #
Lifting of the
Eq
class to unary type constructors.
Since: base-4.9.0.0
Instances
Eq1 [] |
Since: base-4.9.0.0 |
Eq1 Maybe |
Since: base-4.9.0.0 |
Eq1 Identity |
Since: base-4.9.0.0 |
Eq1 Down |
Since: base-4.12.0.0 |
Eq1 NonEmpty |
Since: base-4.10.0.0 |
Eq1 IntMap |
Since: containers-0.5.9 |
Eq1 Tree |
Since: containers-0.5.9 |
Eq1 Seq |
Since: containers-0.5.9 |
Eq1 Set |
Since: containers-0.5.9 |
Eq1 Hashed | |
Eq1 Concrete Source # | |
Eq1 Symbolic Source # | |
Eq a => Eq1 ( Either a) |
Since: base-4.9.0.0 |
Eq a => Eq1 ( (,) a) |
Since: base-4.9.0.0 |
Eq1 ( Proxy :: Type -> Type ) |
Since: base-4.9.0.0 |
Eq k => Eq1 ( Map k) |
Since: containers-0.5.9 |
Eq1 m => Eq1 ( MaybeT m) | |
Eq1 m => Eq1 ( ListT m) | |
Eq a => Eq1 ( Const a :: Type -> Type ) |
Since: base-4.9.0.0 |
( Eq e, Eq1 m) => Eq1 ( ExceptT e m) | |
( Eq w, Eq1 m) => Eq1 ( WriterT w m) | |
( Eq e, Eq1 m) => Eq1 ( ErrorT e m) | |
Eq1 f => Eq1 ( IdentityT f) | |
( Eq w, Eq1 m) => Eq1 ( WriterT w m) | |
Eq1 ( Tagged s) | |
( Eq1 f, Eq1 g) => Eq1 ( Product f g) |
Since: base-4.9.0.0 |
( Eq1 f, Eq1 g) => Eq1 ( Sum f g) |
Since: base-4.9.0.0 |
( Eq1 f, Eq1 g) => Eq1 ( Compose f g) |
Since: base-4.9.0.0 |
eq1 :: ( Eq1 f, Eq a) => f a -> f a -> Bool Source #
Lift the standard
(
function through the type constructor.
==
)
Since: base-4.9.0.0
class Eq1 f => Ord1 (f :: Type -> Type ) Source #
Lifting of the
Ord
class to unary type constructors.
Since: base-4.9.0.0
Instances
Ord1 [] |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering ) -> [a] -> [b] -> Ordering Source # |
|
Ord1 Maybe |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
|
Ord1 Identity |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
|
Ord1 Down |
Since: base-4.12.0.0 |
Defined in Data.Functor.Classes |
|
Ord1 NonEmpty |
Since: base-4.10.0.0 |
Defined in Data.Functor.Classes |
|
Ord1 IntMap |
Since: containers-0.5.9 |
Defined in Data.IntMap.Internal |
|
Ord1 Tree |
Since: containers-0.5.9 |
Ord1 Seq |
Since: containers-0.5.9 |
Defined in Data.Sequence.Internal |
|
Ord1 Set |
Since: containers-0.5.9 |
Defined in Data.Set.Internal |
|
Ord1 Hashed | |
Defined in Data.Hashable.Class |
|
Ord1 Concrete Source # | |
Defined in Hedgehog.Internal.State |
|
Ord1 Symbolic Source # | |
Defined in Hedgehog.Internal.State |
|
Ord a => Ord1 ( Either a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
|
Ord a => Ord1 ( (,) a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftCompare :: (a0 -> b -> Ordering ) -> (a, a0) -> (a, b) -> Ordering Source # |
|
Ord1 ( Proxy :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
|
Ord k => Ord1 ( Map k) |
Since: containers-0.5.9 |
Defined in Data.Map.Internal |
|
Ord1 m => Ord1 ( MaybeT m) | |
Defined in Control.Monad.Trans.Maybe |
|
Ord1 m => Ord1 ( ListT m) | |
Defined in Control.Monad.Trans.List |
|
Ord a => Ord1 ( Const a :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Classes |
|
( Ord e, Ord1 m) => Ord1 ( ExceptT e m) | |
Defined in Control.Monad.Trans.Except |
|
( Ord w, Ord1 m) => Ord1 ( WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy |
|
( Ord e, Ord1 m) => Ord1 ( ErrorT e m) | |
Defined in Control.Monad.Trans.Error |
|
Ord1 f => Ord1 ( IdentityT f) | |
Defined in Control.Monad.Trans.Identity |
|
( Ord w, Ord1 m) => Ord1 ( WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict |
|
Ord1 ( Tagged s) | |
Defined in Data.Tagged |
|
( Ord1 f, Ord1 g) => Ord1 ( Product f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Product |
|
( Ord1 f, Ord1 g) => Ord1 ( Sum f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum |
|
( Ord1 f, Ord1 g) => Ord1 ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose |
compare1 :: ( Ord1 f, Ord a) => f a -> f a -> Ordering Source #
Lift the standard
compare
function through the type constructor.
Since: base-4.9.0.0
class Show1 (f :: Type -> Type ) Source #
Lifting of the
Show
class to unary type constructors.
Since: base-4.9.0.0
Instances
Show1 [] |
Since: base-4.9.0.0 |
Show1 Maybe |
Since: base-4.9.0.0 |
Show1 Identity |
Since: base-4.9.0.0 |
Show1 Down |
Since: base-4.12.0.0 |
Show1 NonEmpty |
Since: base-4.10.0.0 |
Show1 IntMap |
Since: containers-0.5.9 |
Show1 Tree |
Since: containers-0.5.9 |
Show1 Seq |
Since: containers-0.5.9 |
Show1 Set |
Since: containers-0.5.9 |
Show1 Hashed | |
Show1 Concrete Source # | |
Show1 Symbolic Source # | |
Show a => Show1 ( Either a) |
Since: base-4.9.0.0 |
Show a => Show1 ( (,) a) |
Since: base-4.9.0.0 |
Show1 ( Proxy :: Type -> Type ) |
Since: base-4.9.0.0 |
Show k => Show1 ( Map k) |
Since: containers-0.5.9 |
Show1 m => Show1 ( MaybeT m) | |
Show1 m => Show1 ( ListT m) | |
Show1 m => Show1 ( NodeT m) Source # | |
Show1 m => Show1 ( TreeT m) Source # | |
Show a => Show1 ( Const a :: Type -> Type ) |
Since: base-4.9.0.0 |
( Show e, Show1 m) => Show1 ( ExceptT e m) | |
( Show w, Show1 m) => Show1 ( WriterT w m) | |
( Show e, Show1 m) => Show1 ( ErrorT e m) | |
Show1 f => Show1 ( IdentityT f) | |
( Show w, Show1 m) => Show1 ( WriterT w m) | |
Show1 ( Tagged s) | |
( Show1 f, Show1 g) => Show1 ( Product f g) |
Since: base-4.9.0.0 |
( Show1 f, Show1 g) => Show1 ( Sum f g) |
Since: base-4.9.0.0 |
( Show1 f, Show1 g) => Show1 ( Compose f g) |
Since: base-4.9.0.0 |
Deprecated
class HTraversable t where Source #
Deprecated: Replace with Hedgehog.TraversableB (defined in Data.Functor.Barbie) which can be derived automatically using GHC.Generics
Higher-order traversable functors.
Deprecated in favor of
TraversableB
which can be derived using
GHC.Generics
htraverse :: Applicative f => ( forall a. g a -> f (h a)) -> t g -> f (t h) Source #