HMock-0.4.0.0: A flexible mock framework for testing effectful code.
Safe HaskellNone
LanguageHaskell2010

Test.HMock.Predicates

Description

This module defines Predicates which you can use to match the arguments of a method in your execution plan.

Synopsis

Documentation

data Predicate a Source #

A predicate, which tests values and either accepts or rejects them. This is similar to a -> Bool, but also has a Show instance to describe what it is checking.

Predicates are used to define which arguments a general matcher should accept.

Constructors

Predicate 

Fields

Instances

Instances details
Show (Predicate a) Source # 
Instance details

Defined in Test.HMock.Predicates

anything :: Predicate a Source #

A Predicate that accepts anything at all.

>>> accept anything "foo"
True
>>> accept anything undefined
True

eq :: (Show a, Eq a) => a -> Predicate a Source #

A Predicate that accepts only the given value.

>>> accept (eq "foo") "foo"
True
>>> accept (eq "foo") "bar"
False

neq :: (Show a, Eq a) => a -> Predicate a Source #

A Predicate that accepts anything but the given value.

>>> accept (neq "foo") "foo"
False
>>> accept (neq "foo") "bar"
True

gt :: (Show a, Ord a) => a -> Predicate a Source #

A Predicate that accepts anything greater than the given value.

>>> accept (gt 5) 4
False
>>> accept (gt 5) 5
False
>>> accept (gt 5) 6
True

geq :: (Show a, Ord a) => a -> Predicate a Source #

A Predicate that accepts anything greater than or equal to the given value.

>>> accept (geq 5) 4
False
>>> accept (geq 5) 5
True
>>> accept (geq 5) 6
True

lt :: (Show a, Ord a) => a -> Predicate a Source #

A Predicate that accepts anything less than the given value.

>>> accept (lt 5) 4
True
>>> accept (lt 5) 5
False
>>> accept (lt 5) 6
False

leq :: (Show a, Ord a) => a -> Predicate a Source #

A Predicate that accepts anything less than or equal to the given value.

>>> accept (leq 5) 4
True
>>> accept (leq 5) 5
True
>>> accept (leq 5) 6
False

just :: Predicate a -> Predicate (Maybe a) Source #

A Predicate that accepts Maybe values of Just x, where x matches the given child Predicate.

>>> accept (just (eq "value")) Nothing
False
>>> accept (just (eq "value")) (Just "value")
True
>>> accept (just (eq "value")) (Just "wrong value")
False

nothing :: Predicate (Maybe a) Source #

A Predicate that accepts Maybe values of Nothing. Unlike eq, this doesn't require Eq or Show instances.

>>> accept nothing Nothing
True
>>> accept nothing (Just "something")
False

left :: Predicate a -> Predicate (Either a b) Source #

A Predicate that accepts an Either value of Left x, where x matches the given child Predicate.

>>> accept (left (eq "value")) (Left "value")
True
>>> accept (left (eq "value")) (Right "value")
False
>>> accept (left (eq "value")) (Left "wrong value")
False

right :: Predicate b -> Predicate (Either a b) Source #

A Predicate that accepts an Either value of Right x, where x matches the given child Predicate.

>>> accept (right (eq "value")) (Right "value")
True
>>> accept (right (eq "value")) (Right "wrong value")
False
>>> accept (right (eq "value")) (Left "value")
False

zipP :: Predicate a -> Predicate b -> Predicate (a, b) Source #

A Predicate that accepts pairs whose elements satisfy the corresponding child Predicates.

>>> accept (zipP (eq "foo") (eq "bar")) ("foo", "bar")
True
>>> accept (zipP (eq "foo") (eq "bar")) ("bar", "foo")
False

zip3P :: Predicate a -> Predicate b -> Predicate c -> Predicate (a, b, c) Source #

A Predicate that accepts 3-tuples whose elements satisfy the corresponding child Predicates.

>>> accept (zip3P (eq "foo") (eq "bar") (eq "qux")) ("foo", "bar", "qux")
True
>>> accept (zip3P (eq "foo") (eq "bar") (eq "qux")) ("qux", "bar", "foo")
False

zip4P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate (a, b, c, d) Source #

A Predicate that accepts 3-tuples whose elements satisfy the corresponding child Predicates.

>>> accept (zip4P (eq 1) (eq 2) (eq 3) (eq 4)) (1, 2, 3, 4)
True
>>> accept (zip4P (eq 1) (eq 2) (eq 3) (eq 4)) (4, 3, 2, 1)
False

zip5P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate e -> Predicate (a, b, c, d, e) Source #

A Predicate that accepts 3-tuples whose elements satisfy the corresponding child Predicates.

>>> accept (zip5P (eq 1) (eq 2) (eq 3) (eq 4) (eq 5)) (1, 2, 3, 4, 5)
True
>>> accept (zip5P (eq 1) (eq 2) (eq 3) (eq 4) (eq 5)) (5, 4, 3, 2, 1)
False

andP :: Predicate a -> Predicate a -> Predicate a Source #

A Predicate that accepts anything accepted by both of its children.

>>> accept (lt "foo" `andP` gt "bar") "eta"
True
>>> accept (lt "foo" `andP` gt "bar") "quz"
False
>>> accept (lt "foo" `andP` gt "bar") "alpha"
False

orP :: Predicate a -> Predicate a -> Predicate a Source #

A Predicate that accepts anything accepted by either of its children.

>>> accept (lt "bar" `orP` gt "foo") "eta"
False
>>> accept (lt "bar" `orP` gt "foo") "quz"
True
>>> accept (lt "bar" `orP` gt "foo") "alpha"
True

notP :: Predicate a -> Predicate a Source #

A Predicate that inverts another Predicate, accepting whatever its child rejects, and rejecting whatever its child accepts.

>>> accept (notP (eq "negative")) "positive"
True
>>> accept (notP (eq "negative")) "negative"
False

startsWith :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t Source #

A Predicate that accepts sequences that start with the given prefix.

>>> accept (startsWith "fun") "fungible"
True
>>> accept (startsWith "gib") "fungible"
False

endsWith :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t Source #

A Predicate that accepts sequences that end with the given suffix.

>>> accept (endsWith "ow") "crossbow"
True
>>> accept (endsWith "ow") "trebuchet"
False

hasSubstr :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t Source #

A Predicate that accepts sequences that contain the given (consecutive) substring.

>>> accept (hasSubstr "i") "team"
False
>>> accept (hasSubstr "i") "partnership"
True

hasSubsequence :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t Source #

A Predicate that accepts sequences that contain the given (not necessarily consecutive) subsequence.

>>> accept (hasSubsequence [1..5]) [1, 2, 3, 4, 5]
True
>>> accept (hasSubsequence [1..5]) [0, 1, 0, 2, 0, 3, 0, 4, 0, 5, 0]
True
>>> accept (hasSubsequence [1..5]) [2, 3, 5, 7, 11]
False

caseInsensitive :: (MonoFunctor t, MonoFunctor a, Element t ~ Char, Element a ~ Char) => (t -> Predicate a) -> t -> Predicate a Source #

Transforms a Predicate on Strings or string-like types to match without regard to case.

>>> accept (caseInsensitive startsWith "foo") "FOOTBALL!"
True
>>> accept (caseInsensitive endsWith "ball") "soccer"
False
>>> accept (caseInsensitive eq "time") "TIME"
True
>>> accept (caseInsensitive gt "NOTHING") "everything"
False

matchesRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a Source #

A Predicate that accepts Strings or string-like values matching a regular expression. The expression must match the entire argument.

You should not use caseInsensitive matchesRegex, because regular expression syntax itself is still case-sensitive even when the text you are matching is not. Instead, use matchesCaseInsensitiveRegex.

>>> accept (matchesRegex "x{2,5}y?") "xxxy"
True
>>> accept (matchesRegex "x{2,5}y?") "xyy"
False
>>> accept (matchesRegex "x{2,5}y?") "wxxxyz"
False

matchesCaseInsensitiveRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a Source #

A Predicate that accepts Strings or string-like values matching a regular expression in a case-insensitive way. The expression must match the entire argument.

You should use this instead of caseInsensitive matchesRegex, because regular expression syntax itself is still case-sensitive even when the text you are matching is not.

>>> accept (matchesCaseInsensitiveRegex "x{2,5}y?") "XXXY"
True
>>> accept (matchesCaseInsensitiveRegex "x{2,5}y?") "XYY"
False
>>> accept (matchesCaseInsensitiveRegex "x{2,5}y?") "WXXXYZ"
False

containsRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a Source #

A Predicate that accepts Strings or string-like values containing a match for a regular expression. The expression need not match the entire argument.

You should not use caseInsensitive containsRegex, because regular expression syntax itself is still case-sensitive even when the text you are matching is not. Instead, use containsCaseInsensitiveRegex.

>>> accept (containsRegex "x{2,5}y?") "xxxy"
True
>>> accept (containsRegex "x{2,5}y?") "xyy"
False
>>> accept (containsRegex "x{2,5}y?") "wxxxyz"
True

containsCaseInsensitiveRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a Source #

A Predicate that accepts Strings or string-like values containing a match for a regular expression in a case-insensitive way. The expression need match the entire argument.

You should use this instead of caseInsensitive containsRegex, because regular expression syntax itself is still case-sensitive even when the text you are matching is not.

>>> accept (containsCaseInsensitiveRegex "x{2,5}y?") "XXXY"
True
>>> accept (containsCaseInsensitiveRegex "x{2,5}y?") "XYY"
False
>>> accept (containsCaseInsensitiveRegex "x{2,5}y?") "WXXXYZ"
True

isEmpty :: (MonoFoldable t, Show t) => Predicate t Source #

A Predicate that accepts empty data structures.

>>> accept isEmpty ([] :: [Int])
True
>>> accept isEmpty [1, 2, 3]
False
>>> accept isEmpty ""
True
>>> accept isEmpty "gas tank"
False

nonEmpty :: (MonoFoldable t, Show t) => Predicate t Source #

A Predicate that accepts non-empty data structures.

>>> accept nonEmpty ([] :: [Int])
False
>>> accept nonEmpty [1, 2, 3]
True
>>> accept nonEmpty ""
False
>>> accept nonEmpty "gas tank"
True

sizeIs :: (MonoFoldable t, Show t) => Predicate Int -> Predicate t Source #

A Predicate that accepts data structures whose number of elements match the child Predicate.

>>> accept (sizeIs (lt 3)) ['a' .. 'f']
False
>>> accept (sizeIs (lt 3)) ['a' .. 'b']
True

elemsAre :: MonoFoldable t => [Predicate (Element t)] -> Predicate t Source #

A Predicate that accepts data structures whose contents each match the corresponding Predicate in the given list, in the same order.

>>> accept (elemsAre [lt 3, lt 4, lt 5]) [2, 3, 4]
True
>>> accept (elemsAre [lt 3, lt 4, lt 5]) [2, 3, 4, 5]
False
>>> accept (elemsAre [lt 3, lt 4, lt 5]) [2, 10, 4]
False

unorderedElemsAre :: MonoFoldable t => [Predicate (Element t)] -> Predicate t Source #

A Predicate that accepts data structures whose contents each match the corresponding Predicate in the given list, in any order.

>>> accept (unorderedElemsAre [eq 1, eq 2, eq 3]) [1, 2, 3]
True
>>> accept (unorderedElemsAre [eq 1, eq 2, eq 3]) [2, 3, 1]
True
>>> accept (unorderedElemsAre [eq 1, eq 2, eq 3]) [1, 2, 3, 4]
False
>>> accept (unorderedElemsAre [eq 1, eq 2, eq 3]) [1, 3]
False

each :: MonoFoldable t => Predicate (Element t) -> Predicate t Source #

A Predicate that accepts data structures whose elements each match the child Predicate.

>>> accept (each (gt 5)) [4, 5, 6]
False
>>> accept (each (gt 5)) [6, 7, 8]
True
>>> accept (each (gt 5)) []
True

contains :: MonoFoldable t => Predicate (Element t) -> Predicate t Source #

A Predicate that accepts data structures which contain at least one element matching the child Predicate.

>>> accept (contains (gt 5)) [3, 4, 5]
False
>>> accept (contains (gt 5)) [4, 5, 6]
True
>>> accept (contains (gt 5)) []
False

containsAll :: MonoFoldable t => [Predicate (Element t)] -> Predicate t Source #

A Predicate that accepts data structures whose elements all satisfy the given child Predicates.

>>> accept (containsAll [eq "foo", eq "bar"]) ["bar", "foo"]
True
>>> accept (containsAll [eq "foo", eq "bar"]) ["foo"]
False
>>> accept (containsAll [eq "foo", eq "bar"]) ["foo", "bar", "qux"]
True

Each child Predicate must be satisfied by a different element, so repeating a Predicate requires that two different matching elements exist. If you want a Predicate to match multiple elements, instead, you can accomplish this with contains p1 `andP` contains p2 `andP` ....

>>> accept (containsAll [startsWith "f", endsWith "o"]) ["foo"]
False
>>> accept (contains (startsWith "f") `andP` contains (endsWith "o")) ["foo"]
True

containsOnly :: MonoFoldable t => [Predicate (Element t)] -> Predicate t Source #

A Predicate that accepts data structures whose elements all satisfy one of the child Predicates.

>>> accept (containsOnly [eq "foo", eq "bar"]) ["foo"]
True
>>> accept (containsOnly [eq "foo", eq "bar"]) ["foo", "bar"]
True
>>> accept (containsOnly [eq "foo", eq "bar"]) ["foo", "qux"]
False

Each element must satisfy a different child Predicate. If you want multiple elements to match the same Predicate, instead, you can accomplish this with each (p1 `orP` p2 `orP` ...).

>>> accept (containsOnly [eq "foo", eq "bar"]) ["foo", "foo"]
False
>>> accept (each (eq "foo" `orP` eq "bar")) ["foo", "foo"]
True

keys :: (IsList t, Item t ~ (k, v)) => Predicate [k] -> Predicate t Source #

Transforms a Predicate on a list of keys into a Predicate on map-like data structures.

This is equivalent to with (map fst . toList), but more readable.

>>> accept (keys (each (eq "foo"))) [("foo", 5)]
True
>>> accept (keys (each (eq "foo"))) [("foo", 5), ("bar", 6)]
False

values :: (IsList t, Item t ~ (k, v)) => Predicate [v] -> Predicate t Source #

Transforms a Predicate on a list of values into a Predicate on map-like data structures.

This is equivalent to with (map snd . toList), but more readable.

>>> accept (values (each (eq 5))) [("foo", 5), ("bar", 5)]
True
>>> accept (values (each (eq 5))) [("foo", 5), ("bar", 6)]
False

approxEq :: (RealFloat a, Show a) => a -> Predicate a Source #

A Predicate that accepts values of RealFloat types that are close to the given number. The expected precision is scaled based on the target value, so that reasonable rounding error is accepted but grossly inaccurate results are not.

The following naive use of eq fails due to rounding:

>>> accept (eq 1.0) (sum (replicate 100 0.01))
False

The solution is to use approxEq, which accounts for rounding error. However, approxEq doesn't accept results that are far enough off that they likely arise from incorrect calculations instead of rounding error.

>>> accept (approxEq 1.0) (sum (replicate 100 0.01))
True
>>> accept (approxEq 1.0) (sum (replicate 100 0.009999))
False

positive :: (Ord a, Num a) => Predicate a Source #

A Predicate that accepts positive numbers of any Ordered Num type.

>>> accept positive 1
True
>>> accept positive 0
False
>>> accept positive (-1)
False

negative :: (Ord a, Num a) => Predicate a Source #

A Predicate that accepts negative numbers of any Ordered Num type.

>>> accept negative 1
False
>>> accept negative 0
False
>>> accept negative (-1)
True

nonPositive :: (Ord a, Num a) => Predicate a Source #

A Predicate that accepts non-positive numbers of any Ordered Num type.

>>> accept nonPositive 1
False
>>> accept nonPositive 0
True
>>> accept nonPositive (-1)
True

nonNegative :: (Ord a, Num a) => Predicate a Source #

A Predicate that accepts non-negative numbers of any Ordered Num type.

>>> accept nonNegative 1
True
>>> accept nonNegative 0
True
>>> accept nonNegative (-1)
False

finite :: RealFloat a => Predicate a Source #

A Predicate that accepts finite numbers of any RealFloat type.

>>> accept finite 1.0
True
>>> accept finite (0 / 0)
False
>>> accept finite (1 / 0)
False

infinite :: RealFloat a => Predicate a Source #

A Predicate that accepts infinite numbers of any RealFloat type.

>>> accept infinite 1.0
False
>>> accept infinite (0 / 0)
False
>>> accept infinite (1 / 0)
True

nAn :: RealFloat a => Predicate a Source #

A Predicate that accepts NaN values of any RealFloat type.

>>> accept nAn 1.0
False
>>> accept nAn (0 / 0)
True
>>> accept nAn (1 / 0)
False

is :: HasCallStack => (a -> Bool) -> Predicate a Source #

A conversion from a -> Bool to Predicate. This is a fallback that can be used to build a Predicate that checks anything at all. However, its description will be less helpful than standard Predicates.

>>> accept (is even) 3
False
>>> accept (is even) 4
True

qIs :: HasCallStack => ExpQ -> ExpQ Source #

A Template Haskell splice that acts like is, but receives a quoted expression at compile time and has a more helpful description for error messages.

>>> accept $(qIs [| even |]) 3
False
>>> accept $(qIs [| even |]) 4
True
>>> show $(qIs [| even |])
"even"

with :: HasCallStack => (a -> b) -> Predicate b -> Predicate a Source #

A combinator to lift a Predicate to work on a property or computed value of the original value.

>>> accept (with abs (gt 5)) (-6)
True
>>> accept (with abs (gt 5)) (-5)
False
>>> accept (with reverse (eq "olleh")) "hello"
True
>>> accept (with reverse (eq "olleh")) "goodbye"
False

qWith :: ExpQ -> ExpQ Source #

A Template Haskell splice that acts like is, but receives a quoted typed expression at compile time and has a more helpful description for error messages.

>>> accept ($(qWith [| abs |]) (gt 5)) (-6)
True
>>> accept ($(qWith [| abs |]) (gt 5)) (-5)
False
>>> accept ($(qWith [| reverse |]) (eq "olleh")) "hello"
True
>>> accept ($(qWith [| reverse |]) (eq "olleh")) "goodbye"
False
>>> show ($(qWith [| abs |]) (gt 5))
"abs: > 5"

qMatch :: PatQ -> ExpQ Source #

A Template Haskell splice that turns a quoted pattern into a predicate that accepts values that match the pattern.

>>> accept $(qMatch [p| Just (Left _) |]) Nothing
False
>>> accept $(qMatch [p| Just (Left _) |]) (Just (Left 5))
True
>>> accept $(qMatch [p| Just (Left _) |]) (Just (Right 5))
False
>>> show $(qMatch [p| Just (Left _) |])
"Just (Left _)"

typed :: forall a b. (Typeable a, Typeable b) => Predicate a -> Predicate b Source #

Converts a Predicate to a new type. Typically used with visible type application, as in the examples below.

>>> accept (typed @String anything) "foo"
True
>>> accept (typed @String (sizeIs (gt 5))) "foo"
False
>>> accept (typed @String anything) (42 :: Int)
False