| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Predicates
Description
Synopsis
- data Predicate a = Predicate {
- showPredicate :: String
- showNegation :: String
- accept :: a -> Bool
- explain :: a -> String
- (==~) :: Predicate a -> a -> Bool
- anything :: Predicate a
- eq :: (Show a, Eq a) => a -> Predicate a
- neq :: (Show a, Eq a) => a -> Predicate a
- gt :: (Show a, Ord a) => a -> Predicate a
- geq :: (Show a, Ord a) => a -> Predicate a
- lt :: (Show a, Ord a) => a -> Predicate a
- leq :: (Show a, Ord a) => a -> Predicate a
- just :: Predicate a -> Predicate (Maybe a)
- nothing :: Predicate (Maybe a)
- left :: Predicate a -> Predicate (Either a b)
- right :: Predicate b -> Predicate (Either a b)
- zipP :: Predicate a -> Predicate b -> Predicate (a, b)
- zip3P :: Predicate a -> Predicate b -> Predicate c -> Predicate (a, b, c)
- zip4P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate (a, b, c, d)
- zip5P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate e -> Predicate (a, b, c, d, e)
- andP :: Predicate a -> Predicate a -> Predicate a
- orP :: Predicate a -> Predicate a -> Predicate a
- notP :: Predicate a -> Predicate a
- matchesRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a
- matchesCaseInsensitiveRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a
- containsRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a
- containsCaseInsensitiveRegex :: (RegexLike Regex a, Eq a, Show a) => String -> Predicate a
- startsWith :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t
- endsWith :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t
- hasSubstr :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t
- hasSubsequence :: (Show t, IsSequence t, Eq (Element t)) => t -> Predicate t
- caseInsensitive :: (MonoFunctor t, MonoFunctor a, Element t ~ Char, Element a ~ Char) => (t -> Predicate a) -> t -> Predicate a
- isEmpty :: (MonoFoldable t, Show t) => Predicate t
- nonEmpty :: (MonoFoldable t, Show t) => Predicate t
- sizeIs :: (MonoFoldable t, Show t) => Predicate Int -> Predicate t
- elemsAre :: MonoFoldable t => [Predicate (Element t)] -> Predicate t
- unorderedElemsAre :: MonoFoldable t => [Predicate (Element t)] -> Predicate t
- each :: MonoFoldable t => Predicate (Element t) -> Predicate t
- contains :: MonoFoldable t => Predicate (Element t) -> Predicate t
- containsAll :: MonoFoldable t => [Predicate (Element t)] -> Predicate t
- containsOnly :: MonoFoldable t => [Predicate (Element t)] -> Predicate t
- keys :: (IsList t, Item t ~ (k, v)) => Predicate [k] -> Predicate t
- values :: (IsList t, Item t ~ (k, v)) => Predicate [v] -> Predicate t
- approxEq :: (RealFloat a, Show a) => a -> Predicate a
- positive :: (Ord a, Num a) => Predicate a
- negative :: (Ord a, Num a) => Predicate a
- nonPositive :: (Ord a, Num a) => Predicate a
- nonNegative :: (Ord a, Num a) => Predicate a
- finite :: RealFloat a => Predicate a
- infinite :: RealFloat a => Predicate a
- nAn :: RealFloat a => Predicate a
- is :: HasCallStack => (a -> Bool) -> Predicate a
- qIs :: HasCallStack => ExpQ -> ExpQ
- with :: HasCallStack => (a -> b) -> Predicate b -> Predicate a
- qWith :: ExpQ -> ExpQ
- inBranch :: String -> (a -> Maybe b) -> Predicate b -> Predicate a
- qADT :: Name -> ExpQ
- qMatch :: PatQ -> ExpQ
- typed :: forall a b. (Typeable a, Typeable b) => Predicate a -> Predicate b
The Predicate type
A predicate, which tests values and either accepts or rejects them. This
is similar to a -> , but also can describe itself and explain why an
argument does or doesn't match.Bool
Constructors
| Predicate | |
Fields
| |
(==~) :: Predicate a -> a -> Bool Source #
An infix synonym for accept.
>>>eq 1 ==~ 1True>>>eq 2 ==~ 1False
Predicate combinators
Basic predicates
anything :: Predicate a Source #
A Predicate that accepts anything at all.
>>>accept anything "foo"True>>>accept anything undefinedTrue
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) 4False>>>accept (gt 5) 5False>>>accept (gt 5) 6True
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) 4False>>>accept (geq 5) 5True>>>accept (geq 5) 6True
lt :: (Show a, Ord a) => a -> Predicate a Source #
A Predicate that accepts anything less than the given value.
>>>accept (lt 5) 4True>>>accept (lt 5) 5False>>>accept (lt 5) 6False
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) 4True>>>accept (leq 5) 5True>>>accept (leq 5) 6False
Zips
zip4P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate (a, b, c, d) Source #
zip5P :: Predicate a -> Predicate b -> Predicate c -> Predicate d -> Predicate e -> Predicate (a, b, c, d, e) Source #
Logic
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
Regular expressions
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 , because regular
expression syntax itself is still case-sensitive even when the text you are
matching is not. Instead, use caseInsensitive matchesRegexmatchesCaseInsensitiveRegex.
>>>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 , because
regular expression syntax itself is still case-sensitive even when the text
you are matching is not.caseInsensitive matchesRegex
>>>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 , because regular
expression syntax itself is still case-sensitive even when the text you are
matching is not. Instead, use caseInsensitive containsRegexcontainsCaseInsensitiveRegex.
>>>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 , because
regular expression syntax itself is still case-sensitive even when the text
you are matching is not.caseInsensitive containsRegex
>>>accept (containsCaseInsensitiveRegex "x{2,5}y?") "XXXY"True>>>accept (containsCaseInsensitiveRegex "x{2,5}y?") "XYY"False>>>accept (containsCaseInsensitiveRegex "x{2,5}y?") "WXXXYZ"True
Strings and sequences
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
Containers
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
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
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
Numerics
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
Miscellaneous
is :: HasCallStack => (a -> Bool) -> Predicate a Source #
A conversion from a -> to BoolPredicate. 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. You can use
qIs instead to get better descriptions using Template Haskell.
>>>accept (is even) 3False>>>accept (is even) 4True
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 explanation.
>>>accept $(qIs [| even |]) 3False>>>accept $(qIs [| even |]) 4True
>>>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. The explanations are less helpful that standard
predicates like sizeIs. You can use qWith instead to get better
explanations using Template Haskell.
>>>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 with, but receives a quoted
typed expression at compile time and has a more helpful explanation.
>>>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"
inBranch :: String -> (a -> Maybe b) -> Predicate b -> Predicate a Source #
A Predicate that accepts values with a given nested value. This is
intended to match constructors with arguments. You can use qADT instead
to get better explanations using Template Haskell.
>>>accept (inBranch "Left" (\case {Left x -> Just x; _ -> Nothing}) positive) (Left 1)True>>>accept (inBranch "Left" (\case {Left x -> Just x; _ -> Nothing}) positive) (Left 0)False>>>accept (inBranch "Left" (\case {Left x -> Just x; _ -> Nothing}) positive) (Right 1)False
A Template Haskell splice which, given a constructor for an abstract data
type, writes a Predicate that matches on that constructor and applies other
Predicates to its fields.
>>>accept $(qADT 'Nothing) NothingTrue>>>accept $(qADT 'Nothing) (Just 5)False>>>accept ($(qADT 'Just) positive) (Just 5)True>>>accept ($(qADT 'Just) positive) NothingFalse>>>accept ($(qADT 'Just) positive) (Just 0)False
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 _) |]) NothingFalse>>>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