Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- 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 ()
- discover :: TExpQ Group
- checkParallel :: MonadIO m => Group -> m Bool
- checkSequential :: MonadIO m => Group -> m Bool
- withTests :: TestLimit -> Property -> Property
- data TestLimit
- withDiscards :: DiscardLimit -> Property -> Property
- data DiscardLimit
- withShrinks :: ShrinkLimit -> Property -> Property
- data ShrinkLimit
- withRetries :: ShrinkRetries -> Property -> Property
- data ShrinkRetries
- type Gen = GenT Identity
- data GenT m a
- class Monad 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 ()
- (===) :: (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
- 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
- evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a
- data Command n m (state :: (* -> *) -> *) = (HTraversable input, Show (input Symbolic), Typeable output) => Command {
- commandGen :: state Symbolic -> Maybe (n (input Symbolic))
- commandExecute :: input Concrete -> m output
- commandCallbacks :: [Callback input output state]
- data Callback input output state
- data Action m (state :: (* -> *) -> *)
- data 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 ()
- data 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
- distribute :: (Distributive g, Transformer f g m) => g (f m) a -> f (g m) a
- class HTraversable t where
- class Eq1 (f :: * -> *)
- eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool
- class Eq1 f => Ord1 (f :: * -> *)
- compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering
- class Show1 (f :: * -> *)
- showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS
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.
MonadTrans PropertyT Source # | |
Distributive PropertyT Source # | |
MonadBase b m => MonadBase b (PropertyT m) Source # | |
MonadState s m => MonadState s (PropertyT m) Source # | |
MonadReader r m => MonadReader r (PropertyT m) Source # | |
MonadError e m => MonadError e (PropertyT m) Source # | |
Monad m => Monad (PropertyT m) Source # | |
Functor m => Functor (PropertyT m) Source # | |
Monad m => Applicative (PropertyT m) Source # | |
MonadIO m => MonadIO (PropertyT m) Source # | |
MonadPlus m => Alternative (PropertyT m) Source # | |
MonadPlus m => MonadPlus (PropertyT m) Source # | |
MonadCatch m => MonadCatch (PropertyT m) Source # | |
MonadThrow m => MonadThrow (PropertyT m) Source # | |
PrimMonad m => PrimMonad (PropertyT m) Source # | |
Monad m => MonadTest (PropertyT m) Source # | |
MFunctor * PropertyT Source # | |
type Transformer t PropertyT m Source # | |
type PrimState (PropertyT m) Source # | |
A named collection of property tests.
Group | |
|
data PropertyName Source #
The name of a property.
Can be constructed using OverloadedStrings
:
"apples" :: PropertyName
The name of a group of properties.
Can be constructed using OverloadedStrings
:
"fruit" :: GroupName
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
.
One use case for this is writing tests which use ResourceT
:
property $ do n <- forAll $ Gen.int64 Range.linearBounded test . runResourceT $ do -- test with resource usage here
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) ]
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
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
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
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
Generating Test Data
Monad transformer which can generate random values of a
.
MMonad GenT Source # | |
MonadTrans GenT Source # | |
Distributive GenT Source # | |
MonadBase b m => MonadBase b (GenT m) Source # | |
MonadWriter w m => MonadWriter w (GenT m) Source # | |
MonadState s m => MonadState s (GenT m) Source # | |
MonadReader r m => MonadReader r (GenT m) Source # | |
MonadError e m => MonadError e (GenT m) Source # | |
Monad m => Monad (GenT m) Source # | |
Functor m => Functor (GenT m) Source # | |
Monad m => Applicative (GenT m) Source # | |
MonadIO m => MonadIO (GenT m) Source # | |
Monad m => Alternative (GenT m) Source # | |
Monad m => MonadPlus (GenT m) Source # | |
MonadCatch m => MonadCatch (GenT m) Source # | |
MonadThrow m => MonadThrow (GenT m) Source # | |
PrimMonad m => PrimMonad (GenT m) Source # | |
MonadResource m => MonadResource (GenT m) Source # | |
Monad m => MonadGen (GenT m) Source # | |
MFunctor * GenT Source # | |
(Monad m, Semigroup a) => Semigroup (GenT m a) Source # | |
(Monad m, Monoid a) => Monoid (GenT m a) Source # | |
type Transformer t GenT m Source # | |
type PrimState (GenT m) Source # | |
class Monad m => MonadGen m where Source #
Class of monads which can generate input data for tests.
The functions on this class can, and should, be used without their Gen
suffix by importing Hedgehog.Gen qualified.
liftGen :: Gen a -> m a Source #
See Gen.
lift
shrinkGen :: (a -> [a]) -> m a -> m a Source #
See Gen.
shrink
pruneGen :: m a -> m a Source #
See Gen.
prune
scaleGen :: (Size -> Size) -> m a -> m a Source #
See Gen.
scale
freezeGen :: m a -> m (a, m a) Source #
See Gen.
freeze
MonadGen m => MonadGen (MaybeT m) Source # | |
Monad m => MonadGen (GenT m) Source # | |
MonadGen m => MonadGen (ExceptT x m) Source # | |
(MonadGen m, Monoid w) => MonadGen (WriterT w m) Source # | |
MonadGen m => MonadGen (StateT s m) Source # | |
MonadGen m => MonadGen (IdentityT * m) Source # | |
MonadGen m => MonadGen (StateT s m) Source # | |
(MonadGen m, Monoid w) => MonadGen (WriterT w m) Source # | |
MonadGen m => MonadGen (ReaderT * r m) Source # | |
(MonadGen m, Monoid w) => MonadGen (RWST r w s m) Source # | |
(MonadGen m, Monoid w) => MonadGen (RWST r w s m) Source # | |
Tests are parameterized by the size of the randomly-generated data, the meaning of which depends on the particular generator used.
A splittable random number generator.
Tests
A test monad transformer allows the assertion of expectations.
MonadTrans TestT Source # | |
MonadTransControl TestT Source # | |
Distributive TestT Source # | |
MonadBase b m => MonadBase b (TestT m) Source # | |
MonadBaseControl b m => MonadBaseControl b (TestT m) Source # | |
MonadState s m => MonadState s (TestT m) Source # | |
MonadReader r m => MonadReader r (TestT m) Source # | |
MonadError e m => MonadError e (TestT m) Source # | |
Monad m => Monad (TestT m) Source # | |
Functor m => Functor (TestT m) Source # | |
Monad m => Applicative (TestT m) Source # | |
MonadIO m => MonadIO (TestT m) Source # | |
MonadCatch m => MonadCatch (TestT m) Source # | |
MonadThrow m => MonadThrow (TestT m) Source # | |
PrimMonad m => PrimMonad (TestT m) Source # | |
MonadResource m => MonadResource (TestT m) Source # | |
Monad m => MonadTest (TestT m) Source # | |
MFunctor * TestT Source # | |
type StT TestT a Source # | |
type Transformer t TestT m Source # | |
type PrimState (TestT m) Source # | |
type StM (TestT m) a Source # | |
class Monad m => MonadTest m where Source #
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 (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 (ReaderT * r 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
.
(===) :: (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.
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).
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 #
evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a Source #
State Machine Tests
data Command n m (state :: (* -> *) -> *) Source #
The specification for the expected behaviour of an Action
.
(HTraversable input, Show (input Symbolic), 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 :: (* -> *) -> *) Source #
An instantiation of a Command
which can be executed, and its effect
evaluated.
data Sequential m state Source #
A sequence of actions to execute.
Sequential | |
|
Show (Sequential m state) Source # | |
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.
Var (v a) |
Symbolic values.
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)
Transformers
distribute :: (Distributive g, Transformer f g m) => g (f m) a -> f (g m) a Source #
Distribute one monad transformer over another.
Functors
class HTraversable t where Source #
Higher-order traversable functors.
This is used internally to make symbolic variables concrete given an Environment
.
htraverse :: Applicative f => (forall a. g a -> f (h a)) -> t g -> f (t h) Source #
HTraversable (Var a) Source # | |
Lifting of the Eq
class to unary type constructors.
Since: 4.9.0.0
Eq1 [] | Since: 4.9.0.0 |
Eq1 Maybe | Since: 4.9.0.0 |
Eq1 NonEmpty | Since: 4.10.0.0 |
Eq1 Identity | Since: 4.9.0.0 |
Eq1 IntMap | |
Eq1 Tree | |
Eq1 Seq | |
Eq1 Set | |
Eq1 Concrete # | |
Eq1 Symbolic # | |
Eq a => Eq1 (Either a) | Since: 4.9.0.0 |
Eq a => Eq1 ((,) a) | Since: 4.9.0.0 |
Eq1 (Proxy *) | Since: 4.9.0.0 |
Eq k => Eq1 (Map k) | |
Eq1 m => Eq1 (MaybeT m) | |
Eq1 m => Eq1 (ListT m) | |
Eq a => Eq1 (Const * a) | Since: 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 f, Eq1 g) => Eq1 (Product * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Sum * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) | Since: 4.9.0.0 |
eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool #
Lift the standard (
function through the type constructor.==
)
Since: 4.9.0.0
class Eq1 f => Ord1 (f :: * -> *) #
Lifting of the Ord
class to unary type constructors.
Since: 4.9.0.0
Ord1 [] | Since: 4.9.0.0 |
Ord1 Maybe | Since: 4.9.0.0 |
Ord1 NonEmpty | Since: 4.10.0.0 |
Ord1 Identity | Since: 4.9.0.0 |
Ord1 IntMap | |
Ord1 Tree | |
Ord1 Seq | |
Ord1 Set | |
Ord1 Concrete # | |
Ord1 Symbolic # | |
Ord a => Ord1 (Either a) | Since: 4.9.0.0 |
Ord a => Ord1 ((,) a) | Since: 4.9.0.0 |
Ord1 (Proxy *) | Since: 4.9.0.0 |
Ord k => Ord1 (Map k) | |
Ord1 m => Ord1 (MaybeT m) | |
Ord1 m => Ord1 (ListT m) | |
Ord a => Ord1 (Const * a) | Since: 4.9.0.0 |
(Ord e, Ord1 m) => Ord1 (ExceptT e m) | |
(Ord w, Ord1 m) => Ord1 (WriterT w m) | |
(Ord e, Ord1 m) => Ord1 (ErrorT e m) | |
Ord1 f => Ord1 (IdentityT * f) | |
(Ord w, Ord1 m) => Ord1 (WriterT w m) | |
(Ord1 f, Ord1 g) => Ord1 (Product * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Sum * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) | Since: 4.9.0.0 |
compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering #
Lift the standard compare
function through the type constructor.
Since: 4.9.0.0
Lifting of the Show
class to unary type constructors.
Since: 4.9.0.0
Show1 [] | Since: 4.9.0.0 |
Show1 Maybe | Since: 4.9.0.0 |
Show1 NonEmpty | Since: 4.10.0.0 |
Show1 Identity | Since: 4.9.0.0 |
Show1 IntMap | |
Show1 Tree | |
Show1 Seq | |
Show1 Set | |
Show1 Concrete # | |
Show1 Symbolic # | |
Show a => Show1 (Either a) | Since: 4.9.0.0 |
Show a => Show1 ((,) a) | Since: 4.9.0.0 |
Show1 (Proxy *) | Since: 4.9.0.0 |
Show k => Show1 (Map k) | |
Show1 m => Show1 (MaybeT m) | |
Show1 m => Show1 (ListT m) | |
Show1 m => Show1 (Node m) # | |
Show1 m => Show1 (Tree m) # | |
Show a => Show1 (Const * a) | Since: 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 f, Show1 g) => Show1 (Product * f g) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Sum * f g) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Compose * * f g) | Since: 4.9.0.0 |