hedgehog-0.4: Hedgehog will eat all your bugs.

Safe HaskellNone
LanguageHaskell98

Hedgehog

Contents

Description

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

Documentation

data Group Source #

A named collection of property tests.

Constructors

Group 

data Property Source #

A property test to check, along with some configurable limits like how many times to run the test.

data Test m a Source #

A property test.

Instances

MonadTrans Test Source # 

Methods

lift :: Monad m => m a -> Test m a #

Distributive Test Source # 

Associated Types

type Transformer (f :: (* -> *) -> * -> *) (Test :: (* -> *) -> * -> *) (m :: * -> *) :: Constraint Source #

Methods

distribute :: Transformer f Test m => Test (f m) a -> f (Test m) a Source #

MonadBase b m => MonadBase b (Test m) Source # 

Methods

liftBase :: b α -> Test m α #

MonadError e m => MonadError e (Test m) Source # 

Methods

throwError :: e -> Test m a #

catchError :: Test m a -> (e -> Test m a) -> Test m a #

MonadReader r m => MonadReader r (Test m) Source # 

Methods

ask :: Test m r #

local :: (r -> r) -> Test m a -> Test m a #

reader :: (r -> a) -> Test m a #

MonadState s m => MonadState s (Test m) Source # 

Methods

get :: Test m s #

put :: s -> Test m () #

state :: (s -> (a, s)) -> Test m a #

Monad m => Monad (Test m) Source # 

Methods

(>>=) :: Test m a -> (a -> Test m b) -> Test m b #

(>>) :: Test m a -> Test m b -> Test m b #

return :: a -> Test m a #

fail :: String -> Test m a #

Functor m => Functor (Test m) Source # 

Methods

fmap :: (a -> b) -> Test m a -> Test m b #

(<$) :: a -> Test m b -> Test m a #

Monad m => Applicative (Test m) Source # 

Methods

pure :: a -> Test m a #

(<*>) :: Test m (a -> b) -> Test m a -> Test m b #

(*>) :: Test m a -> Test m b -> Test m b #

(<*) :: Test m a -> Test m b -> Test m a #

MonadIO m => MonadIO (Test m) Source # 

Methods

liftIO :: IO a -> Test m a #

Monad m => Alternative (Test m) Source # 

Methods

empty :: Test m a #

(<|>) :: Test m a -> Test m a -> Test m a #

some :: Test m a -> Test m [a] #

many :: Test m a -> Test m [a] #

Monad m => MonadPlus (Test m) Source # 

Methods

mzero :: Test m a #

mplus :: Test m a -> Test m a -> Test m a #

MonadCatch m => MonadCatch (Test m) Source # 

Methods

catch :: Exception e => Test m a -> (e -> Test m a) -> Test m a #

MonadThrow m => MonadThrow (Test m) Source # 

Methods

throwM :: Exception e => e -> Test m a #

PrimMonad m => PrimMonad (Test m) Source # 

Associated Types

type PrimState (Test m :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (Test m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (Test m)), a#)) -> Test m a #

MonadResource m => MonadResource (Test m) Source # 

Methods

liftResourceT :: ResourceT IO a -> Test m a #

MFunctor * Test Source # 

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #

type Transformer t Test m Source # 
type PrimState (Test m) Source # 
type PrimState (Test m) = PrimState m

data TestLimit Source #

The number of successful tests that need to be run before a property test is considered successful.

Instances

Enum TestLimit Source # 
Eq TestLimit Source # 
Integral TestLimit Source # 
Num TestLimit Source # 
Ord TestLimit Source # 
Real TestLimit Source # 
Show TestLimit Source # 
Lift TestLimit Source # 

Methods

lift :: TestLimit -> Q Exp #

data DiscardLimit Source #

The number of discards to allow before giving up.

Instances

Enum DiscardLimit Source # 
Eq DiscardLimit Source # 
Integral DiscardLimit Source # 
Num DiscardLimit Source # 
Ord DiscardLimit Source # 
Real DiscardLimit Source # 
Show DiscardLimit Source # 
Lift DiscardLimit Source # 

Methods

lift :: DiscardLimit -> Q Exp #

data ShrinkLimit Source #

The number of shrinks to try before giving up on shrinking.

Instances

Enum ShrinkLimit Source # 
Eq ShrinkLimit Source # 
Integral ShrinkLimit Source # 
Num ShrinkLimit Source # 
Ord ShrinkLimit Source # 
Real ShrinkLimit Source # 
Show ShrinkLimit Source # 
Lift ShrinkLimit Source # 

Methods

lift :: ShrinkLimit -> Q Exp #

data Gen m a Source #

Generator for random values of a.

Instances

MMonad Gen Source # 

Methods

embed :: Monad n => (forall a. m a -> Gen n a) -> Gen m b -> Gen n b #

MonadTrans Gen Source # 

Methods

lift :: Monad m => m a -> Gen m a #

Distributive Gen Source # 

Associated Types

type Transformer (f :: (* -> *) -> * -> *) (Gen :: (* -> *) -> * -> *) (m :: * -> *) :: Constraint Source #

Methods

distribute :: Transformer f Gen m => Gen (f m) a -> f (Gen m) a Source #

MonadBase b m => MonadBase b (Gen m) Source # 

Methods

liftBase :: b α -> Gen m α #

MonadError e m => MonadError e (Gen m) Source # 

Methods

throwError :: e -> Gen m a #

catchError :: Gen m a -> (e -> Gen m a) -> Gen m a #

MonadReader r m => MonadReader r (Gen m) Source # 

Methods

ask :: Gen m r #

local :: (r -> r) -> Gen m a -> Gen m a #

reader :: (r -> a) -> Gen m a #

MonadState s m => MonadState s (Gen m) Source # 

Methods

get :: Gen m s #

put :: s -> Gen m () #

state :: (s -> (a, s)) -> Gen m a #

MonadWriter w m => MonadWriter w (Gen m) Source # 

Methods

writer :: (a, w) -> Gen m a #

tell :: w -> Gen m () #

listen :: Gen m a -> Gen m (a, w) #

pass :: Gen m (a, w -> w) -> Gen m a #

Monad m => Monad (Gen m) Source # 

Methods

(>>=) :: Gen m a -> (a -> Gen m b) -> Gen m b #

(>>) :: Gen m a -> Gen m b -> Gen m b #

return :: a -> Gen m a #

fail :: String -> Gen m a #

Functor m => Functor (Gen m) Source # 

Methods

fmap :: (a -> b) -> Gen m a -> Gen m b #

(<$) :: a -> Gen m b -> Gen m a #

Monad m => Applicative (Gen m) Source # 

Methods

pure :: a -> Gen m a #

(<*>) :: Gen m (a -> b) -> Gen m a -> Gen m b #

(*>) :: Gen m a -> Gen m b -> Gen m b #

(<*) :: Gen m a -> Gen m b -> Gen m a #

MonadIO m => MonadIO (Gen m) Source # 

Methods

liftIO :: IO a -> Gen m a #

Monad m => Alternative (Gen m) Source # 

Methods

empty :: Gen m a #

(<|>) :: Gen m a -> Gen m a -> Gen m a #

some :: Gen m a -> Gen m [a] #

many :: Gen m a -> Gen m [a] #

Monad m => MonadPlus (Gen m) Source # 

Methods

mzero :: Gen m a #

mplus :: Gen m a -> Gen m a -> Gen m a #

MonadCatch m => MonadCatch (Gen m) Source # 

Methods

catch :: Exception e => Gen m a -> (e -> Gen m a) -> Gen m a #

MonadThrow m => MonadThrow (Gen m) Source # 

Methods

throwM :: Exception e => e -> Gen m a #

PrimMonad m => PrimMonad (Gen m) Source # 

Associated Types

type PrimState (Gen m :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (Gen m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (Gen m)), a#)) -> Gen m a #

MonadResource m => MonadResource (Gen m) Source # 

Methods

liftResourceT :: ResourceT IO a -> Gen m a #

MFunctor * Gen Source # 

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #

type Transformer t Gen m Source # 
type Transformer t Gen m = (Monad (t (Gen m)), Transformer t MaybeT m, Transformer t Tree (MaybeT m))
type PrimState (Gen m) Source # 
type PrimState (Gen m) = PrimState m

data Range a Source #

A range describes the bounds of a number to generate, which may or may not be dependent on a Size.

Instances

Functor Range Source # 

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

newtype Size Source #

Tests are parameterized by the size of the randomly-generated data, the meaning of which depends on the particular generator used.

Constructors

Size 

Fields

Instances

Enum Size Source # 

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Integral Size Source # 

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size Source # 

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Real Size Source # 

Methods

toRational :: Size -> Rational #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

data Seed Source #

A splittable random number generator.

Constructors

Seed 

Fields

Instances

Eq Seed Source # 

Methods

(==) :: Seed -> Seed -> Bool #

(/=) :: Seed -> Seed -> Bool #

Ord Seed Source # 

Methods

compare :: Seed -> Seed -> Ordering #

(<) :: Seed -> Seed -> Bool #

(<=) :: Seed -> Seed -> Bool #

(>) :: Seed -> Seed -> Bool #

(>=) :: Seed -> Seed -> Bool #

max :: Seed -> Seed -> Seed #

min :: Seed -> Seed -> Seed #

Read Seed Source # 
Show Seed Source # 

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

RandomGen Seed Source # 

Methods

next :: Seed -> (Int, Seed) #

genRange :: Seed -> (Int, Int) #

split :: Seed -> (Seed, Seed) #

Property

property :: Test IO () -> Property Source #

Creates a property to check.

withTests :: TestLimit -> Property -> Property Source #

Set the number times a property should be executed before it is considered successful.

withDiscards :: DiscardLimit -> Property -> Property Source #

Set the number times a property is allowed to discard before the test runner gives up.

withShrinks :: ShrinkLimit -> Property -> Property Source #

Set the number times a property is allowed to shrink before the test runner gives up and prints the counterexample.

check :: MonadIO m => Property -> m Bool Source #

Check a property.

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)
    ]

Test

forAll :: (Monad m, Show a, HasCallStack) => Gen m a -> Test m a Source #

Generates a random input for the test by running the provided generator.

forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen m a -> Test m a Source #

Generates a random input for the test by running the provided generator.

This is a the same as forAll but allows the user to provide a custom rendering function. This is useful for values which don't have a Show instance.

annotate :: (Monad m, HasCallStack) => String -> Test m () Source #

Annotates the source code with a message that might be useful for debugging a test failure.

annotateShow :: (Monad m, Show a, HasCallStack) => a -> Test m () Source #

Annotates the source code with a value that might be useful for debugging a test failure.

footnote :: Monad m => String -> Test m () Source #

Logs a message to be displayed as additional information in the footer of the failure report.

footnoteShow :: (Monad m, Show a) => a -> Test m () Source #

Logs a value to be displayed as additional information in the footer of the failure report.

success :: Monad m => Test m () Source #

Another name for pure ().

discard :: Monad m => Test m a Source #

Discards a test entirely.

failure :: (Monad m, HasCallStack) => Test m a Source #

Causes a test to fail.

assert :: (Monad m, HasCallStack) => Bool -> Test m () Source #

Fails the test if the condition provided is False.

(===) :: (Monad m, Eq a, Show a, HasCallStack) => a -> a -> Test m () infix 4 Source #

Fails the test if the two arguments provided are not equal.

liftCatch :: (MonadCatch m, HasCallStack) => m a -> Test m a Source #

Fails the test if the action throws an exception.

/The benefit of using this over lift is that the location of the exception will be shown in the output./

liftCatchIO :: (MonadIO m, HasCallStack) => IO a -> Test m a Source #

Fails the test if the action throws an exception.

/The benefit of using this over liftIO is that the location of the exception will be shown in the output./

liftEither :: (Monad m, Show x, HasCallStack) => Either x a -> Test m a Source #

Fails the test if the Either is Left, otherwise returns the value in the Right.

liftExceptT :: (Monad m, Show x, HasCallStack) => ExceptT x m a -> Test m a Source #

Fails the test if the ExceptT is Left, otherwise returns the value in the Right.

withCatch :: (MonadCatch m, HasCallStack) => Test m a -> Test 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 withCatch will be shown in the output./

withExceptT :: (Monad m, Show x, HasCallStack) => Test (ExceptT x m) a -> Test m a Source #

Fails the test if the ExceptT is Left, otherwise returns the value in the Right.

withResourceT :: MonadResourceBase m => Test (ResourceT m) a -> Test m a Source #

Run a computation which requires resource acquisition / release.

Note that if you allocate anything before a forAll you will likely encounter unexpected behaviour, due to the way ResourceT interacts with the control flow introduced by shrinking.

tripping :: HasCallStack => Applicative f => Monad m => Show b => Show (f a) => Eq (f a) => a -> (a -> b) -> (b -> f a) -> Test m () Source #

Test that a pair of encode / decode functions are compatible.

Abstract State Machine

data Command n m state Source #

The specification for the expected behaviour of an Action.

Constructors

(HTraversable input, Show (input Symbolic), Typeable output) => Command 

Fields

data Callback input output m state Source #

Optional command configuration.

Constructors

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 -> v output -> 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 Symbolic values when we are generating actions, and Concrete values when we are executing them.

Ensure (state Concrete -> input Concrete -> output -> Test m ())

A post-condition for a command that must be verified for the command to be considered a success.

data Action m state Source #

An instantiation of a Command which can be executed, and its effect evaluated.

Instances

Show (Action m state) Source # 

Methods

showsPrec :: Int -> Action m state -> ShowS #

show :: Action m state -> String #

showList :: [Action m state] -> ShowS #

executeSequential :: forall m state. (HasCallStack, MonadCatch m) => (forall v. state v) -> [Action m state] -> Test 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 actions combinator in the Hedgehog.Gen module.

newtype Concrete a where Source #

Concrete values.

Constructors

Concrete :: a -> Concrete a 

Instances

Functor Concrete Source # 

Methods

fmap :: (a -> b) -> Concrete a -> Concrete b #

(<$) :: a -> Concrete b -> Concrete a #

Foldable Concrete Source # 

Methods

fold :: Monoid m => Concrete m -> m #

foldMap :: Monoid m => (a -> m) -> Concrete a -> m #

foldr :: (a -> b -> b) -> b -> Concrete a -> b #

foldr' :: (a -> b -> b) -> b -> Concrete a -> b #

foldl :: (b -> a -> b) -> b -> Concrete a -> b #

foldl' :: (b -> a -> b) -> b -> Concrete a -> b #

foldr1 :: (a -> a -> a) -> Concrete a -> a #

foldl1 :: (a -> a -> a) -> Concrete a -> a #

toList :: Concrete a -> [a] #

null :: Concrete a -> Bool #

length :: Concrete a -> Int #

elem :: Eq a => a -> Concrete a -> Bool #

maximum :: Ord a => Concrete a -> a #

minimum :: Ord a => Concrete a -> a #

sum :: Num a => Concrete a -> a #

product :: Num a => Concrete a -> a #

Traversable Concrete Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Concrete a -> f (Concrete b) #

sequenceA :: Applicative f => Concrete (f a) -> f (Concrete a) #

mapM :: Monad m => (a -> m b) -> Concrete a -> m (Concrete b) #

sequence :: Monad m => Concrete (m a) -> m (Concrete a) #

Eq1 Concrete Source # 

Methods

liftEq :: (a -> b -> Bool) -> Concrete a -> Concrete b -> Bool #

Ord1 Concrete Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Concrete a -> Concrete b -> Ordering #

Show1 Concrete Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Concrete a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Concrete a] -> ShowS #

Eq a => Eq (Concrete a) Source # 

Methods

(==) :: Concrete a -> Concrete a -> Bool #

(/=) :: Concrete a -> Concrete a -> Bool #

Ord a => Ord (Concrete a) Source # 

Methods

compare :: Concrete a -> Concrete a -> Ordering #

(<) :: Concrete a -> Concrete a -> Bool #

(<=) :: Concrete a -> Concrete a -> Bool #

(>) :: Concrete a -> Concrete a -> Bool #

(>=) :: Concrete a -> Concrete a -> Bool #

max :: Concrete a -> Concrete a -> Concrete a #

min :: Concrete a -> Concrete a -> Concrete a #

Show a => Show (Concrete a) Source # 

Methods

showsPrec :: Int -> Concrete a -> ShowS #

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

data Symbolic a where Source #

Symbolic values.

Constructors

Symbolic :: Typeable a => Var -> Symbolic a 

Instances

Eq1 Symbolic Source # 

Methods

liftEq :: (a -> b -> Bool) -> Symbolic a -> Symbolic b -> Bool #

Ord1 Symbolic Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Symbolic a -> Symbolic b -> Ordering #

Show1 Symbolic Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Symbolic a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Symbolic a] -> ShowS #

Eq (Symbolic a) Source # 

Methods

(==) :: Symbolic a -> Symbolic a -> Bool #

(/=) :: Symbolic a -> Symbolic a -> Bool #

Ord (Symbolic a) Source # 

Methods

compare :: Symbolic a -> Symbolic a -> Ordering #

(<) :: Symbolic a -> Symbolic a -> Bool #

(<=) :: Symbolic a -> Symbolic a -> Bool #

(>) :: Symbolic a -> Symbolic a -> Bool #

(>=) :: Symbolic a -> Symbolic a -> Bool #

max :: Symbolic a -> Symbolic a -> Symbolic a #

min :: Symbolic a -> Symbolic a -> Symbolic a #

Show (Symbolic a) Source # 

Methods

showsPrec :: Int -> Symbolic a -> ShowS #

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

data Var Source #

Symbolic variable names.

Instances

Eq Var Source # 

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Num Var Source # 

Methods

(+) :: Var -> Var -> Var #

(-) :: Var -> Var -> Var #

(*) :: Var -> Var -> Var #

negate :: Var -> Var #

abs :: Var -> Var #

signum :: Var -> Var #

fromInteger :: Integer -> Var #

Ord Var Source # 

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

newtype Opaque a Source #

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 Ref v =
    Ref (v (Opaque (IORef Int)))

Constructors

Opaque 

Fields

Instances

Eq a => Eq (Opaque a) Source # 

Methods

(==) :: Opaque a -> Opaque a -> Bool #

(/=) :: Opaque a -> Opaque a -> Bool #

Ord a => Ord (Opaque a) Source # 

Methods

compare :: Opaque a -> Opaque a -> Ordering #

(<) :: Opaque a -> Opaque a -> Bool #

(<=) :: Opaque a -> Opaque a -> Bool #

(>) :: Opaque a -> Opaque a -> Bool #

(>=) :: Opaque a -> Opaque a -> Bool #

max :: Opaque a -> Opaque a -> Opaque a #

min :: Opaque a -> Opaque a -> Opaque a #

Show (Opaque a) Source # 

Methods

showsPrec :: Int -> Opaque a -> ShowS #

show :: Opaque a -> String #

showList :: [Opaque a] -> ShowS #

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.

Minimal complete definition

htraverse

Methods

htraverse :: Applicative f => (forall a. g a -> f (h a)) -> t g -> f (t h) Source #

class Eq1 f #

Lifting of the Eq class to unary type constructors.

Minimal complete definition

liftEq

Instances

Eq1 [] 

Methods

liftEq :: (a -> b -> Bool) -> [a] -> [b] -> Bool #

Eq1 Maybe 

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Eq1 Identity 

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Eq1 Concrete # 

Methods

liftEq :: (a -> b -> Bool) -> Concrete a -> Concrete b -> Bool #

Eq1 Symbolic # 

Methods

liftEq :: (a -> b -> Bool) -> Symbolic a -> Symbolic b -> Bool #

Eq a => Eq1 (Either a) 

Methods

liftEq :: (a -> b -> Bool) -> Either a a -> Either a b -> Bool #

Eq a => Eq1 ((,) a) 

Methods

liftEq :: (a -> b -> Bool) -> (a, a) -> (a, b) -> Bool #

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool #

Eq1 m => Eq1 (ListT m) 

Methods

liftEq :: (a -> b -> Bool) -> ListT m a -> ListT m b -> Bool #

Eq1 m => Eq1 (MaybeT m) 

Methods

liftEq :: (a -> b -> Bool) -> MaybeT m a -> MaybeT m b -> Bool #

Eq a => Eq1 (Const * a) 

Methods

liftEq :: (a -> b -> Bool) -> Const * a a -> Const * a b -> Bool #

(Eq w, Eq1 m) => Eq1 (WriterT w m) 

Methods

liftEq :: (a -> b -> Bool) -> WriterT w m a -> WriterT w m b -> Bool #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool #

(Eq e, Eq1 m) => Eq1 (ErrorT e m) 

Methods

liftEq :: (a -> b -> Bool) -> ErrorT e m a -> ErrorT e m b -> Bool #

Eq1 f => Eq1 (IdentityT * f) 

Methods

liftEq :: (a -> b -> Bool) -> IdentityT * f a -> IdentityT * f b -> Bool #

(Eq w, Eq1 m) => Eq1 (WriterT w m) 

Methods

liftEq :: (a -> b -> Bool) -> WriterT w m a -> WriterT w m b -> Bool #

(Eq1 f, Eq1 g) => Eq1 (Product * f g) 

Methods

liftEq :: (a -> b -> Bool) -> Product * f g a -> Product * f g b -> Bool #

(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) 

Methods

liftEq :: (a -> b -> Bool) -> Compose * * f g a -> Compose * * f g b -> Bool #

eq1 :: (Eq1 f, Eq a) => f a -> f a -> Bool #

Lift the standard (==) function through the type constructor.

class Eq1 f => Ord1 f #

Lifting of the Ord class to unary type constructors.

Minimal complete definition

liftCompare

Instances

Ord1 [] 

Methods

liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering #

Ord1 Maybe 

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Ord1 Identity 

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Ord1 Concrete # 

Methods

liftCompare :: (a -> b -> Ordering) -> Concrete a -> Concrete b -> Ordering #

Ord1 Symbolic # 

Methods

liftCompare :: (a -> b -> Ordering) -> Symbolic a -> Symbolic b -> Ordering #

Ord a => Ord1 (Either a) 

Methods

liftCompare :: (a -> b -> Ordering) -> Either a a -> Either a b -> Ordering #

Ord a => Ord1 ((,) a) 

Methods

liftCompare :: (a -> b -> Ordering) -> (a, a) -> (a, b) -> Ordering #

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering #

Ord1 m => Ord1 (ListT m) 

Methods

liftCompare :: (a -> b -> Ordering) -> ListT m a -> ListT m b -> Ordering #

Ord1 m => Ord1 (MaybeT m) 

Methods

liftCompare :: (a -> b -> Ordering) -> MaybeT m a -> MaybeT m b -> Ordering #

Ord a => Ord1 (Const * a) 

Methods

liftCompare :: (a -> b -> Ordering) -> Const * a a -> Const * a b -> Ordering #

(Ord w, Ord1 m) => Ord1 (WriterT w m) 

Methods

liftCompare :: (a -> b -> Ordering) -> WriterT w m a -> WriterT w m b -> Ordering #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering #

(Ord e, Ord1 m) => Ord1 (ErrorT e m) 

Methods

liftCompare :: (a -> b -> Ordering) -> ErrorT e m a -> ErrorT e m b -> Ordering #

Ord1 f => Ord1 (IdentityT * f) 

Methods

liftCompare :: (a -> b -> Ordering) -> IdentityT * f a -> IdentityT * f b -> Ordering #

(Ord w, Ord1 m) => Ord1 (WriterT w m) 

Methods

liftCompare :: (a -> b -> Ordering) -> WriterT w m a -> WriterT w m b -> Ordering #

(Ord1 f, Ord1 g) => Ord1 (Product * f g) 

Methods

liftCompare :: (a -> b -> Ordering) -> Product * f g a -> Product * f g b -> Ordering #

(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) 

Methods

liftCompare :: (a -> b -> Ordering) -> Compose * * f g a -> Compose * * f g b -> Ordering #

compare1 :: (Ord1 f, Ord a) => f a -> f a -> Ordering #

Lift the standard compare function through the type constructor.

class Show1 f #

Lifting of the Show class to unary type constructors.

Minimal complete definition

liftShowsPrec

Instances

Show1 [] 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [[a]] -> ShowS #

Show1 Maybe 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Show1 Identity 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Show1 Concrete # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Concrete a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Concrete a] -> ShowS #

Show1 Symbolic # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Symbolic a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Symbolic a] -> ShowS #

Show a => Show1 (Either a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Either a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Either a a] -> ShowS #

Show a => Show1 ((,) a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (a, a) -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(a, a)] -> ShowS #

Show1 (Proxy *)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Show1 m => Show1 (ListT m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ListT m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ListT m a] -> ShowS #

Show1 m => Show1 (MaybeT m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> MaybeT m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [MaybeT m a] -> ShowS #

Show1 m => Show1 (Node m) # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Node m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Node m a] -> ShowS #

Show1 m => Show1 (Tree m) # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree m a] -> ShowS #

Show a => Show1 (Const * a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Const * a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Const * a a] -> ShowS #

(Show w, Show1 m) => Show1 (WriterT w m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> WriterT w m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [WriterT w m a] -> ShowS #

(Show e, Show1 m) => Show1 (ExceptT e m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS #

(Show e, Show1 m) => Show1 (ErrorT e m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ErrorT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ErrorT e m a] -> ShowS #

Show1 f => Show1 (IdentityT * f) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> IdentityT * f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [IdentityT * f a] -> ShowS #

(Show w, Show1 m) => Show1 (WriterT w m) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> WriterT w m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [WriterT w m a] -> ShowS #

(Show1 f, Show1 g) => Show1 (Product * f g) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product * f g a] -> ShowS #

(Show1 f, Show1 g) => Show1 (Compose * * f g) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose * * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose * * f g a] -> ShowS #

showsPrec1 :: (Show1 f, Show a) => Int -> f a -> ShowS #

Lift the standard showsPrec and showList functions through the type constructor.