hedgehog-0.1: 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 run your properies:

tests :: IO Bool
tests =
  $$(checkConcurrent)

You can then load the module in GHCi, and run it:

>>> tests
━━━ Test.Example ━━━
  ✓ prop_reverse passed 100 tests.

Synopsis

Documentation

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 #

MFunctor Test Source # 

Methods

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

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 #

MonadThrow m => MonadThrow (Test m) Source # 

Methods

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

MonadCatch m => MonadCatch (Test m) Source # 

Methods

catch :: Exception e => Test m a -> (e -> Test m a) -> 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

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

MonadTrans Gen Source # 

Methods

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

MMonad Gen Source # 

Methods

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

MFunctor Gen Source # 

Methods

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

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 #

MonadThrow m => MonadThrow (Gen m) Source # 

Methods

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

MonadCatch m => MonadCatch (Gen m) Source # 

Methods

catch :: Exception e => Gen m a -> (e -> Gen m a) -> 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

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.

checkSequential :: TExpQ (IO Bool) Source #

Check all the properties in a file sequentially.

tests :: IO Bool
tests =
  $$(checkSequential)

checkConcurrent :: TExpQ (IO Bool) Source #

Check all the properties in a file concurrently.

tests :: IO Bool
tests =
  $$(checkConcurrent)

recheck :: MonadIO m => Size -> Seed -> Property -> m () Source #

Check a property using a specific size and seed.

Test

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

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

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

Logs an information message to be displayed if the test fails.

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.

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.

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 (f a) => Eq (f a) => a -> (a -> b) -> (b -> f a) -> Test m () Source #

Test that a pair of render / parse functions are compatible.