Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library provides sets of properties that should hold for common typeclasses.
Note: functions that test laws of a subclass never test the laws of
a superclass. For example, commutativeSemigroupLaws
never tests
the laws provided by semigroupLaws
.
Synopsis
- lawsCheck :: Laws -> IO Bool
- lawsCheckOne :: Gen a -> [Gen a -> Laws] -> IO Bool
- lawsCheckMany :: [(String, [Laws])] -> IO Bool
- binaryLaws :: (Binary a, Eq a, Show a) => Gen a -> Laws
- bitsLaws :: (FiniteBits a, Show a) => Gen a -> Laws
- eqLaws :: (Eq a, Show a) => Gen a -> Laws
- integralLaws :: (Integral a, Show a) => Gen a -> Laws
- monoidLaws :: (Eq a, Monoid a, Show a) => Gen a -> Laws
- commutativeMonoidLaws :: (Eq a, Monoid a, Show a) => Gen a -> Laws
- ordLaws :: forall a. (Ord a, Show a) => Gen a -> Laws
- enumLaws :: (Enum a, Eq a, Show a) => Gen a -> Laws
- boundedEnumLaws :: (Bounded a, Enum a, Eq a, Show a) => Gen a -> Laws
- semigroupLaws :: (Eq a, Semigroup a, Show a) => Gen a -> Laws
- commutativeSemigroupLaws :: (Eq a, Semigroup a, Show a) => Gen a -> Laws
- exponentialSemigroupLaws :: (Eq a, Semigroup a, Show a) => Gen a -> Laws
- idempotentSemigroupLaws :: (Eq a, Semigroup a, Show a) => Gen a -> Laws
- rectangularBandSemigroupLaws :: (Eq a, Semigroup a, Show a) => Gen a -> Laws
- jsonLaws :: (FromJSON a, ToJSON a, Eq a, Show a) => Gen a -> Laws
- genericLaws :: (Generic a, Eq a, Show a, Eq (Rep a x), Show (Rep a x)) => Gen a -> Gen (Rep a x) -> Laws
- semiringLaws :: (Semiring a, Eq a, Show a) => Gen a -> Laws
- ringLaws :: (Ring a, Eq a, Show a) => Gen a -> Laws
- starLaws :: (Star a, Eq a, Show a) => Gen a -> Laws
- showLaws :: Show a => Gen a -> Laws
- showReadLaws :: (Eq a, Read a, Show a) => Gen a -> Laws
- storableLaws :: (Eq a, Show a, Storable a) => Gen a -> Laws
- alternativeLaws :: (Alternative f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- applicativeLaws :: (Applicative f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- contravariantLaws :: (Contravariant f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- foldableLaws :: (Foldable f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- functorLaws :: (Functor f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- monadLaws :: (Monad f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- monadIOLaws :: (MonadIO f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- monadPlusLaws :: (MonadPlus f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- monadZipLaws :: (MonadZip f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- traversableLaws :: (Traversable f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws
- arrowLaws :: forall f. (Arrow f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- bifoldableLaws :: forall f. (Bifoldable f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- bifoldableFunctorLaws :: forall f. (Bifoldable f, Bifunctor f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- bifunctorLaws :: forall f. (Bifunctor f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- bitraversableLaws :: forall f. (Bitraversable f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- categoryLaws :: forall f. (Category f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- commutativeCategoryLaws :: forall f. (Category f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws
- data Laws = Laws {
- lawsTypeClass :: String
- lawsProperties :: [(String, Property)]
- data LawContext = LawContext {}
- data Context
- contextualise :: LawContext -> Context
- hLessThan :: (MonadTest m, Ord a, Show a, HasCallStack) => a -> a -> m ()
- hGreaterThan :: (MonadTest m, Ord a, Show a, HasCallStack) => a -> a -> m ()
- heq :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> m ()
- heq1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> m ()
- heq2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> m ()
- heqCtx :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> Context -> m ()
- heqCtx1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> Context -> m ()
- heqCtx2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> Context -> m ()
- hneq :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> m ()
- hneq1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> m ()
- hneq2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> m ()
- hneqCtx :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> Context -> m ()
- hneqCtx1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> Context -> m ()
- hneqCtx2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> Context -> m ()
Running
A convenience function for testing the properties of a typeclass. For example, in GHCi:
>>>
genOrdering :: Gen Ordering; genOrdering = frequency [(1,pure EQ),(1,pure LT),(1,pure GT)]
>>>
lawsCheck (monoidLaws genOrdering)
Monoid: Left Identity ✓ <interactive> passed 100 tests. Monoid: Right Identity ✓ <interactive> passed 100 tests. Monoid: Associativity ✓ <interactive> passed 100 tests. Monoid: Concatenation ✓ <interactive> passed 100 tests. True
:: Gen a | The generator for your type. |
-> [Gen a -> Laws] | Functions that take a generator and output |
-> IO Bool |
A convenience function for testing many typeclass instances of a single type.
>>>
lawsCheckOne (word8 constantBounded) [jsonLaws, showReadLaws]
ToJSON/FromJSON: Partial Isomorphism ✓ <interactive> passed 100 tests. ToJSON/FromJSON: Encoding equals value ✓ <interactive> passed 100 tests. Show/Read: Partial Isomorphism: show/read ✓ <interactive> passed 100 tests. Show/Read: Partial Isomorphism: show/read with initial space ✓ <interactive> passed 100 tests. Show/Read: Partial Isomorphism: showsPrec/readsPrec ✓ <interactive> passed 100 tests. Show/Read: Partial Isomorphism: showList/readList ✓ <interactive> passed 100 tests. Show/Read: Partial Isomorphism: showListWith shows/readListDefault ✓ <interactive> passed 100 tests. True
A convenience function for checking many typeclass instances of multiple types.
import Control.Applicative (liftA2) import Data.Map (Map) import Data.Set (Set) import qualified Data.List as List import qualified Data.Set as Set import qualified Data.Map as Map import qualified Hedgehog.Gen as Gen import qualified Hedgehog.Range as Range import Hedgehog (Gen) import Hedgehog.Classes -- Generate a smallSet Int
genSet :: Gen (Set Int) genSet = Set.fromList <$> (Gen.list (Range.linear 2 10) (Gen.int Range.constantBounded)) -- Generate a smallMap String Int
genMap :: Gen (Map String Int) genMap = Map.fromList <$> (liftA2 List.zip genStrings genInts) where rng = Range.linear 2 6 genStrings = Gen.list rng (Gen.string rng Gen.lower) genInts = Gen.list rng (Gen.int Range.constantBounded) commonLaws :: (Eq a, Monoid a, Show a) => Gen a -> [Laws] commonLaws p = [eqLaws p, monoidLaws p] tests :: [(String, [Laws])] tests = [ ("Set Int", commonLaws genSet) , ("Map String Int", commonLaws genMap) ]
Now, in GHCi:
>>>
lawsCheckMany tests
Testing properties for common typeclasses... ------------- -- Set Int -- ------------- Eq: Transitive ✓ interactive passed 100 tests. Eq: Symmetric ✓ interactive passed 100 tests. Eq: Reflexive ✓ interactive passed 100 tests. Eq: Negation ✓ interactive passed 100 tests. Monoid: Left Identity ✓ interactive passed 100 tests. Monoid: Right Identity ✓ interactive passed 100 tests. Monoid: Associativity ✓ interactive passed 100 tests. Monoid: Concatenation ✓ interactive passed 100 tests. -------------------- -- Map String Int -- -------------------- Eq: Transitive ✓ interactive passed 100 tests. Eq: Symmetric ✓ interactive passed 100 tests. Eq: Reflexive ✓ interactive passed 100 tests. Eq: Negation ✓ interactive passed 100 tests. Monoid: Left Identity ✓ interactive passed 100 tests. Monoid: Right Identity ✓ interactive passed 100 tests. Monoid: Associativity ✓ interactive passed 100 tests. Monoid: Concatenation ✓ interactive passed 100 tests. All tests succeeded True
Properties
Ground types
bitsLaws :: (FiniteBits a, Show a) => Gen a -> Laws Source #
Tests the following Bits
laws:
- Conjunction Idempotence
n
≡.&.
nn
- Disjunction Idempotence
n
≡.|.
nn
- Double Complement
≡complement
.
complement
id
- Set Bit
setBit
n i ≡ n.|.
bit
i- Clear Bit
≡clearBit
n in
.&.
complement
(bit
i)- Complement Bit
≡complement
n ixor
n (bit
i)- Clear Zero
≡clearBit
zeroBits
izeroBits
- Set Zero
≡setBit
zeroBits
izeroBits
- Test Zero
≡testBit
zeroBits
iFalse
- Pop Zero
≡popCount
zeroBits
0
- Count Leading Zeros of Zero
≡countLeadingZeros
zeroBits
finiteBitSize
(undefined
:: a)- Count Trailing Zeros of Zero
≡countTrailingZeros
zeroBits
finiteBitSize
(undefined
:: a)
genericLaws :: (Generic a, Eq a, Show a, Eq (Rep a x), Show (Rep a x)) => Gen a -> Gen (Rep a x) -> Laws Source #
semiringLaws :: (Semiring a, Eq a, Show a) => Gen a -> Laws Source #
Tests the following Semiring
laws:
- Additive Left Identity
≡zero
+
xx
- Additive Right Identity
x
≡+
zero
x
- Additive Associativity
x
≡+
(y+
z)(x
+
y)+
z- Additive Commutativity
x
≡+
yy
+
x- Multiplicative Left Identity
≡one
*
xx
- Multiplicative Right Identity
x
≡*
one
x
- Multiplicative Associativity
x
≡*
(y*
z)(x
*
y)*
z- Multiplicatiion Left-Distributes Over Addtion
x
≡*
(y+
z)(x
*
y)+
(x*
z)- Multiplication Right-Distibutes Over Addition
(y
≡+
z)*
x(y
*
x)+
(z*
x)- Multiplicative Left Annihilation
≡zero
*
xzero
- Multiplicative Right Annihilation
x
≡*
zero
zero
showReadLaws :: (Eq a, Read a, Show a) => Gen a -> Laws Source #
Tests the following Show
/ Read
laws:
- Partial Isomorphism: show/read
≡readMaybe
.
show
Just
- Partial Isomorphism: show/read with initial space
≡readMaybe
.
(" "++
).
show
Just
- Partial Isomorphism: showsPrec/readPrec
(a,"")
≡elem
readsPrec
p (showsPrec
p a "")True
- Partial Isomorphism: showList/readList
(as,"")
≡elem
readList
(showList
as "")True
- Partial Isomorphism: showListWith shows/readListDefault
(as,"")
≡elem
readListDefault
(showListWith
shows
as "")True
storableLaws :: (Eq a, Show a, Storable a) => Gen a -> Laws Source #
Tests the following Storable
laws:
- Set-Get
≡pokeElemOff
ptr ix a>>
peekElemOff
ptr ixpure
a- Get-Set
≡peekElemOff
ptr ix>>=
pokeElemOff
ptr ix
(Putting back what you got out has no effect)pure
()- List Conversion Roundtrips
- Mallocing a list and then reconstructing it gives you the same list
- PeekElemOff/Peek
≡peekElemOff
a ipeek
(plusPtr
a (i*
sizeOf
undefined
))- PokeElemOff/Poke
≡pokeElemOff
a i xpoke
(plusPtr
a (i*
sizeOf
undefined
)) x- PeekByteOff/Peek
≡peekByteOff
a ipeek
(plusPtr
a i)- PokeByteOff/Peek
≡pokeByteOff
a i xpoke
(plusPtr
a i) x
Unary type constructors
alternativeLaws :: (Alternative f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
applicativeLaws :: (Applicative f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
contravariantLaws :: (Contravariant f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
foldableLaws :: (Foldable f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
Tests the following Foldable
laws:
- Fold
fold
≡foldMap
id
- FoldMap
foldMap
f ≡foldr
(mappend
.
f)mempty
- Foldr
foldr
f z t ≡appEndo
(foldMap
(Endo
.
f) t) z- Foldr'
foldr'
f z0 t ≡foldl
f'id
t z0, where f' k x z = k$!
f x z- Foldl
foldl
f z t ≡appEndo
(getDual
(foldMap
(Dual
.
Endo
.
flip
f) t)) z- Foldl'
foldl'
f z0 xs ≡foldr
f'id
xs z0, where f' x k z = k$!
f z x- Foldl1
foldl1
f t ≡ let (x:xs) =toList
t infoldl
f x xs- Foldr1
=foldr1
f t ≡ let (xs,x)unsnoc (
toList
t) infoldr
f x xs- ToList
toList
≡foldr
(:) []- Null
null
≡foldr
(const
(const
False
))True
- Length
length
≡getSum
.
foldMap
(const
(Sum
1))
This additionally tests that the user's implementations of foldr'
and foldl'
are strict in their accumulators.
functorLaws :: (Functor f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
monadLaws :: (Monad f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
monadIOLaws :: (MonadIO f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
monadPlusLaws :: (MonadPlus f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
monadZipLaws :: (MonadZip f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
traversableLaws :: (Traversable f, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => (forall x. Gen x -> Gen (f x)) -> Laws Source #
Tests the following Traversable
laws:
- Naturality
t
≡.
traverse
ftraverse
(t.
f), for every applicative transformation t- Identity
≡traverse
Identity
Identity
- Composition
≡traverse
(Compose
.
fmap
g.
f)Compose
.
fmap
(traverse
g).
traverse
f- SequenceA Naturality
t
≡.
sequenceA
sequenceA
.
fmap
t, for every applicative transformation t- SequenceA Identity
≡sequenceA
.
fmap
Identity
Identity
- SequenceA Composition
≡sequenceA
.
fmap
Compose
Compose
.
fmap
sequenceA
.
sequenceA
- FoldMap
≡foldMap
foldMapDefault
- Fmap
≡fmap
fmapDefault
Binary type constructors
arrowLaws :: forall f. (Arrow f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
Tests the following Arrow
laws:
- Arr Identity
≡arr
id
id
- Arr Composition
≡arr
(f>>>
g)arr
f>>>
arr
g- Arr-First inverse
≡first
(arr
f)arr
(first
f)- First Composition
≡first
(f>>>
g)first
f>>>
first
g- Arrow Law 5
≡first
f>>>
arr
fst
arr
fst
>>>
f- Arrow Law 6
≡first
f>>>
arr
(id
***
g)arr
(id
***
g)>>>
first
f- Arrow Law 7
≡first
(first
f)>>>
arr
assocarr
assoc>>>
first
f, where assoc ((a,b),c) = (a,(b,c))
bifoldableLaws :: forall f. (Bifoldable f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
bifoldableFunctorLaws :: forall f. (Bifoldable f, Bifunctor f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
bifunctorLaws :: forall f. (Bifunctor f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
bitraversableLaws :: forall f. (Bitraversable f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
Tests the following Bitraversable
laws:
- Naturality
≡bitraverse
(t.
f) (t.
g)t
.
bitraverse
f g, for every applicative transformation t- Identity
≡bitraverse
Identity
Identity
Identity
- Composition
≡Compose
.
fmap
(bitraverse
g1 g2).
bitraverse
f1 f2bitraverse
(Compose
.
fmap
g1.
f1) (Compose
.
fmap
g2.
f2)
categoryLaws :: forall f. (Category f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
commutativeCategoryLaws :: forall f. (Category f, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws Source #
Defining your own Laws
A Laws
is the name of the typeclass and the set of named properties associated with that typeclass.
Laws | |
|
data LawContext Source #
The context surrounding the property test of a law. Use contextualise
to turn this into a Context
.
LawContext | |
|
contextualise :: LawContext -> Context Source #
Turn a LawContext
into a Context
.
Hedgehog equality tests sans source information
hLessThan :: (MonadTest m, Ord a, Show a, HasCallStack) => a -> a -> m () Source #
Fails the test if the right argument is less than or equal to the left. see https://github.com/hedgehogqa/haskell-hedgehog/pull/196
hGreaterThan :: (MonadTest m, Ord a, Show a, HasCallStack) => a -> a -> m () Source #
Fails the test if the right argument is greater than or equal to the left. see https://github.com/hedgehogqa/haskell-hedgehog/pull/196
heq :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> m () infix 4 Source #
Passes the test if the given arguments are equal. Otherwise fails
with NoContext
.
heq1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> m () infix 4 Source #
Passes the test if the given arguments are equal. Otherwise fails
with NoContext
.
heq2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> m () infix 4 Source #
Passes the test if the given arguments are equal. Otherwise fails
with NoContext
.
heqCtx :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> Context -> m () Source #
Passes the test if the given arguments are equal. Otherwise fails
with the given Context
.
heqCtx1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> Context -> m () Source #
Passes the test if the given arguments are equal. Otherwise fails
with the given Context
.
heqCtx2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> Context -> m () Source #
Passes the test if the given arguments are equal. Otherwise fails
with the given Context
.
hneq :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> m () infix 4 Source #
Passes the test if the given arguments are not equal. Otherwise fails
with NoContext
.
hneq1 :: (MonadTest m, HasCallStack, Eq a, Show a, forall x. Eq x => Eq (f x), forall x. Show x => Show (f x)) => f a -> f a -> m () Source #
Passes the test if the given arguments are not equal. Otherwise fails
with NoContext
.
hneq2 :: (MonadTest m, HasCallStack, Eq a, Eq b, Show a, Show b, forall x y. (Eq x, Eq y) => Eq (f x y), forall x y. (Show x, Show y) => Show (f x y)) => f a b -> f a b -> m () infix 4 Source #
Passes the test if the given arguments are not equal. Otherwise fails
with NoContext
.
hneqCtx :: (MonadTest m, HasCallStack, Eq a, Show a) => a -> a -> Context -> m () Source #
Passes the test if the given arguments are not equal. Otherwise fails
with the given Context
.