predicate-transformers-0.3.0.0: A library for writing predicates and transformations over predicates in Haskell

Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Documentation

type Pred a = a -> Bool Source #

A convenient alias for predicates.

type FT c a b = (a -> c) -> b -> c Source #

Close to a CPS transform of b -> a, except that c isn't quantified over. Stands for "function transformer".

type PT a b = FT Bool a b Source #

Predicate transformers form a category where composition is ordinary function composition. Multiple are already provided by the standard library, for instance all and any.

match :: APrism s t a b -> PT a s Source #

Operate on the target of a prism, or fail.

getter :: Getting a s a -> FT c a s Source #

Operate on the target of a getter.

nay :: PT a a Source #

Invert a predicate.

just :: PT a (Maybe a) Source #

Operate on the Just branch of a Maybe, or fail.

left :: PT e (Either e a) Source #

Operate on the Left branch of an Either, or fail.

right :: PT a (Either e a) Source #

Operate on the Right branch of an Either, or fail.

endingWith :: Foldable f => PT a (f a) Source #

Operate on the last value in a list, or fail if it's not present.

startingWith :: Foldable f => PT a (f a) Source #

Operate on the first value in a list, or fail if it's not present.

only :: Foldable f => PT a (f a) Source #

Require that a list has a single element, and operate on that element.

dist :: [Pred a] -> Pred [a] 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.

distF :: (Eq (f ()), Functor f, Foldable f) => f (Pred a) -> Pred (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 dist.

distRep :: Representable f => f (a -> Bool) -> f a -> f Bool Source #

Given a representable functor-full of predicates, and a functor-full of values, yield a representable functor-full of booleans. Similar to distF.

checkAll :: Monoid m => [a -> m] -> a -> m Source #

Test all predicates against one value.

sumOver :: (Monoid m, Plated a) => FT m a a Source #

Given a plated type, take a monoidal sum over every child recursively, bottom-up.

(==>) :: a -> b -> (a, b) Source #

Sugar for tupling.

pair :: Pred a -> Pred b -> Pred (a, b) Source #

(!) :: (b -> a) -> FT c a b Source #

Flipped function composition; f ! for a function f is a predicate transformer.

traced :: Show a => FT c a a Source #

Prints the input of a predicate, for debugging.