Safe Haskell | None |
---|---|
Language | Haskell2010 |
PredicateTransformers
Description
This library is based on the notion of a predicate transformer, the below
type PT a b
, which is a function from a
to predicates on b
.
They act as a sort of compositional "matcher language".
Composing these predicate transformers is meant to be analogous to composing optics
and there are utilities for using predicate transformers with (lens
-style) optics.
Some predicate transformers provided by other libraries:
all
, any
(base)
either
(base)
allOf
(lens)
Synopsis
- class Boolish a where
- data PredicateFailed = PredicateFailed !CallStack (Doc ann) actual
- type Pred p a = a -> p
- type PT p a b = Pred p a -> Pred 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
- kth :: (Boolish p, Foldable f) => Int -> PT p a (f a)
- list :: (HasCallStack, Boolish p) => [Pred p a] -> [a] -> p
- predful :: (HasCallStack, Boolish p, Eq (f ()), Functor f, Foldable f) => f (Pred p a) -> Pred p (f a)
- compose :: Representable f => f (Pred p a) -> f a -> f p
- allTrue :: (Boolish p, Foldable f) => f (Pred p a) -> Pred p a
- allOf1 :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s
- pattern (:=>) :: a -> b -> (a, b)
- pair :: Boolish p => Pred p a -> Pred p b -> Pred 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) => Pred p a
- equals :: (HasCallStack, Boolish p, Eq a) => a -> Pred p a
Documentation
class Boolish a where Source #
Class of possible predicate 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.
Methods
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 PredicateFailed Source #
The exception thrown by predicates of type `IO ()` by default. Other IOExceptions will work fine.
Constructors
PredicateFailed !CallStack (Doc ann) actual |
Instances
Exception PredicateFailed Source # | |
Defined in PredicateTransformers Methods toException :: PredicateFailed -> SomeException fromException :: SomeException -> Maybe PredicateFailed displayException :: PredicateFailed -> String | |
Show PredicateFailed Source # | |
Defined in PredicateTransformers Methods showsPrec :: Int -> PredicateFailed -> ShowS show :: PredicateFailed -> String showList :: [PredicateFailed] -> 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 predicate to its contents.
This works for folds, too.
kth :: (Boolish p, Foldable f) => Int -> PT p a (f a) Source #
Only test the k
th element of a foldable.
list :: (HasCallStack, Boolish p) => [Pred p a] -> [a] -> p Source #
Given a list of predicates and a list of values, ensure that each predicate holds for each respective value. Fails if the two lists have different lengths.
predful :: (HasCallStack, Boolish p, Eq (f ()), Functor f, Foldable f) => f (Pred p a) -> Pred p (f a) Source #
Given a functor-full of predicates, and a functor-full of values, ensure that the structures
of the two functors match and apply all of the predicates to all of the values.
Generalized version of list
.
compose :: Representable f => f (Pred p a) -> f a -> f p Source #
Given a representable functor-full of predicates, and a functor-full of values,
yield a representable functor-full of booleans. Similar to predful
.
allTrue :: (Boolish p, Foldable f) => f (Pred p a) -> Pred p a Source #
Test all predicates against one value.
allOf1 :: (HasCallStack, Boolish p) => Getting [a] s a -> PT p a s Source #
Check that a predicate 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 => Pred p a -> Pred p b -> Pred p (a, b) Source #
A pair of predicates, made into a predicate on pairs.
fun :: (a -> b) -> PT p b a Source #
Flipped function composition; pf f
for a function f
is a predicate transformer
such that pf f p i == p (f i)
.
traced :: Show a => (a -> String) -> PT c a a Source #
Prints the input of a predicate, for debugging.
tracedShow :: Show a => PT c a a Source #
Prints the input of a predicate, for debugging.
traceFailShow :: (Boolish p, Show a) => PT p a a Source #
Prints the input of a predicate, if the predicate fails, using Show
.
Requires that the predicate's output type can be checked for failure.
traceFail :: Boolish p => (a -> String) -> PT p a a Source #
Prints the input of a predicate over functions, if the predicate fails. Requires that the predicate's output type can be checked for failure.