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 Predicatory a where
- class Exceptional a where
- assess :: a -> IO () -> a
- data PredicateFailed = PredicateFailed !CallStack (Doc ann) actual
- type Pred p a = a -> p
- type PT p a b = Pred p a -> Pred p b
- predJust :: Predicatory p => PT p a (Maybe a)
- predLeft :: Predicatory p => PT p e (Either e a)
- predRight :: Predicatory p => PT p a (Either e a)
- endingWith :: (HasCallStack, Predicatory p, Foldable f) => PT p a (f a)
- startingWith :: (HasCallStack, Predicatory p, Foldable f) => PT p a (f a)
- soleElementOf :: (HasCallStack, Predicatory p) => Fold s a -> PT p a s
- soleElement :: (Predicatory p, Foldable f) => PT p a (f a)
- match :: Predicatory p => Prism' s a -> PT p a s
- kth :: (Predicatory p, Foldable f) => Int -> PT p a (f a)
- predList :: (HasCallStack, Predicatory p) => [Pred p a] -> [a] -> p
- predful :: (HasCallStack, Predicatory p, Eq (f ()), Functor f, Foldable f) => f (Pred p a) -> Pred p (f a)
- predCompose :: Representable f => f (Pred p a) -> f a -> f p
- allTrue :: (Predicatory p, Foldable f) => f (Pred p a) -> Pred p a
- allOf1 :: (HasCallStack, Predicatory p) => Fold s a -> PT p a s
- pattern (:=>) :: a -> b -> (a, b)
- pair :: Predicatory p => Pred p a -> Pred p b -> Pred p (a, b)
- pt :: (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 :: (Exceptional p, Predicatory p, Show a) => PT p a a
- traceFail :: (Predicatory p, Exceptional p) => (a -> String) -> PT p a a
- something :: Predicatory p => Pred p a
- forced :: (Predicatory p, NFData a) => Pred p a
- equals :: (HasCallStack, Predicatory p, Eq a) => a -> Pred p a
- satAll :: Predicatory p => [Pred p a] -> Pred p a
Documentation
class Predicatory a where Source #
Class of possible predicate results.
This is mostly a lattice with otherHand
as disjunction, also
as conjunction, stop
as the falsy
value, and continue
as the truthy value. There may be multiple falsy values, however.
Methods
otherHand :: a -> a -> a infixr 2 Source #
also :: a -> a -> a infixr 3 Source #
stop :: HasCallStack => v -> Doc ann -> a Source #
Instances
Predicatory Bool Source # | |
a ~ () => Predicatory (IO a) Source # | |
Predicatory a => Predicatory (e -> a) Source # | |
class Exceptional a where Source #
Class of predicate results which can be checked for failure, by triggering an action.
Instances
Exceptional Bool Source # | |
Defined in PredicateTransformers | |
a ~ () => Exceptional (IO a) Source # | |
Defined in PredicateTransformers | |
Exceptional a => Exceptional (e -> a) Source # | |
Defined in PredicateTransformers |
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 |
predJust :: Predicatory p => PT p a (Maybe a) Source #
Operate on the Just
branch of a Maybe
, or fail.
predLeft :: Predicatory p => PT p e (Either e a) Source #
Operate on the Left
branch of an Either
, or fail.
predRight :: Predicatory p => PT p a (Either e a) Source #
Operate on the Right
branch of an Either
, or fail.
endingWith :: (HasCallStack, Predicatory 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, Predicatory p, Foldable f) => PT p a (f a) Source #
Operate on the first value in a foldable, or fail if it's not present.
soleElementOf :: (HasCallStack, Predicatory p) => Fold s a -> PT p a s Source #
Require that a Fold
has a single element, and operate on that element.
soleElement :: (Predicatory p, Foldable f) => PT p a (f a) Source #
Require that a Foldable
has a single element, and operate on that element.
match :: Predicatory p => Prism' s a -> PT p a s Source #
Require that a Prism
matches, and apply the predicate to its contents.
kth :: (Predicatory p, Foldable f) => Int -> PT p a (f a) Source #
Only test the k
th element of a foldable.
predList :: (HasCallStack, Predicatory 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, Predicatory 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
.
predCompose :: 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 :: (Predicatory p, Foldable f) => f (Pred p a) -> Pred p a Source #
Test all predicates against one value.
allOf1 :: (HasCallStack, Predicatory p) => Fold 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 :: Predicatory p => Pred p a -> Pred p b -> Pred p (a, b) Source #
A pair of predicates, made into a predicate on pairs.
pt :: (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 :: (Exceptional p, Predicatory 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 :: (Predicatory p, Exceptional 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.
something :: Predicatory p => Pred p a Source #
Predicate which always succeeds.
forced :: (Predicatory p, NFData a) => Pred p a Source #
Predicate which triggers full evaluation of its input and succeeds. Useful for testing that an exception isn't thrown.
equals :: (HasCallStack, Predicatory p, Eq a) => a -> Pred p a Source #
Predicate on equality.