Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This library is based on the notion of a property transformer, the below
type PT a b
, which is a function from a
to properties on b
.
They act as a sort of compositional "matcher language".
Composing these property transformers is meant to be analogous to composing optics
and there are utilities for using property transformers with (lens-style) optics.
Some property transformers provided by other libraries:
all
, any
(base)
either
(base)
allOf
(lens)
Synopsis
- class Boolish a where
- data PropertyFailed = forall actual ann. PropertyFailed !CallStack (Doc ann) actual
- type Prop p a = a -> p
- type PT p a b = Prop p a -> Prop p b
- endingWith :: (HasCallStack, Boolish p, Foldable f) => PT p a (f a)
- startingWith :: (HasCallStack, Boolish p, Foldable f) => PT p a (f a)
- match :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s
- atIndex :: (Boolish p, Foldable f) => Int -> PT p a (f a)
- list :: (HasCallStack, Boolish p) => [Prop p a] -> [a] -> p
- propful :: (HasCallStack, Boolish p, Eq (f ()), Functor f, Foldable f) => f (Prop p a) -> Prop p (f a)
- compose :: Representable f => f (Prop p a) -> f a -> f p
- allTrue :: (Boolish p, Foldable f) => f (Prop p a) -> Prop p a
- allOf1 :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s
- pattern (:=>) :: a -> b -> (a, b)
- pair :: Boolish p => Prop p a -> Prop p b -> Prop p (a, b)
- fun :: (a -> b) -> PT p b a
- (?) :: (a -> b) -> a -> b
- traced :: Show a => (a -> String) -> PT c a a
- tracedShow :: Show a => PT c a a
- traceFailShow :: (Boolish p, Show a) => PT p a a
- traceFail :: Boolish p => (a -> String) -> PT p a a
- forced :: (Boolish p, NFData a) => Prop p a
- equals :: (HasCallStack, Boolish p, Eq a) => a -> Prop p a
Documentation
class Boolish a where Source #
Class of possible property results.
This is almost a lattice with or
as disjunction, and
as conjunction, fail
as the falsy
value, and succeed
as the truthy value. However there may be multiple falsy values, and
and
will pick the first one it's passed, whereas or
will pick the second it's passed.
or :: a -> a -> a infixr 2 Source #
and :: a -> a -> a infixr 3 Source #
fail :: HasCallStack => Doc ann -> v -> a Source #
assess :: a -> IO () -> a Source #
Check and execute a callback on failure.
data PropertyFailed Source #
The exception thrown by properties of type `IO ()` by default. Other IOExceptions will work fine.
forall actual ann. PropertyFailed !CallStack (Doc ann) actual |
Instances
Exception PropertyFailed Source # | |
Defined in PropertyMatchers | |
Show PropertyFailed Source # | |
Defined in PropertyMatchers showsPrec :: Int -> PropertyFailed -> ShowS # show :: PropertyFailed -> String # showList :: [PropertyFailed] -> ShowS # |
endingWith :: (HasCallStack, Boolish p, Foldable f) => PT p a (f a) Source #
Operate on the last value in a foldable, or fail if it's not present.
startingWith :: (HasCallStack, Boolish p, Foldable f) => PT p a (f a) Source #
Operate on the first value in a foldable, or fail if it's not present.
match :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s Source #
Require that a Prism
matches, and apply the property to its contents.
This works for folds, too.
atIndex :: (Boolish p, Foldable f) => Int -> PT p a (f a) Source #
Test the element of a foldable at some index.
list :: (HasCallStack, Boolish p) => [Prop p a] -> [a] -> p Source #
Given a list of properties and a list of values, ensure that each property holds for each respective value. Fails if the two lists have different lengths.
propful :: (HasCallStack, Boolish p, Eq (f ()), Functor f, Foldable f) => f (Prop p a) -> Prop p (f a) Source #
Given a functor-full of properties, and a functor-full of values, ensure that the structures
of the two functors match and apply all of the properties to all of the values.
Generalized version of list
.
compose :: Representable f => f (Prop p a) -> f a -> f p Source #
Given a representable functor-full of properties, and a functor-full of values,
yield a representable functor-full of booleans. Similar to propful
.
allTrue :: (Boolish p, Foldable f) => f (Prop p a) -> Prop p a Source #
Test all properties against one value.
allOf1 :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s Source #
Check that a property is true for all values behind a generalized getter and that there's at least one value for which it's true.
pair :: Boolish p => Prop p a -> Prop p b -> Prop p (a, b) Source #
A pair of properties, made into a property of pairs.
fun :: (a -> b) -> PT p b a Source #
Flipped function composition; pf f
for a function f
is a property transformer
such that pf f p i == p (f i)
.
(?) :: (a -> b) -> a -> b infixr 8 Source #
Higher precedence $
, to work well with &
.
The intended use is something like `x & match _Right ? equals 2`.
traced :: Show a => (a -> String) -> PT c a a Source #
Prints the input of a property, for debugging.
tracedShow :: Show a => PT c a a Source #
Prints the input of a property, for debugging.
traceFailShow :: (Boolish p, Show a) => PT p a a Source #
Prints the input of a property, if the property fails, using Show
.
Requires that the property's output type can be checked for failure.
traceFail :: Boolish p => (a -> String) -> PT p a a Source #
Prints the input of a property over functions, if the property fails. Requires that the property's output type can be checked for failure.