wai-predicates-0.8.3: WAI request predicates

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Predicate

Contents

Synopsis

Predicate

type Predicate a f t = a -> Result f t Source

A predicate is a function of some value of type a to a Result, i.e. a Bool-like value with Okay as True and Fail as False, which carries additional data in each branch.

constant :: t -> Predicate a f t Source

A predicate which always returns Okay with the given value as metadata.

failure :: f -> Predicate a f t Source

A predicate which always returns Fail with the given value as metadata.

and :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t') Source

A predicate corresponding to the logical AND connective of two predicate.

or :: Predicate a f t -> Predicate a f t -> Predicate a f t Source

A predicate corresponding to the logical OR connective of two predicates. It requires the metadata of each Okay branch to be of the same type.

If both arguments evaluate to Okay the one with the smaller "delta" will be preferred, or--if equal--the left-hand argument.

orElse :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t') Source

A predicate corresponding to the logical OR connective of two predicates. The metadata of each Okay branch can be of different types.

If both arguments evaluate to Okay the one with the smaller "delta" will be preferred, or--if equal--the left-hand argument.

(.&.) :: Predicate a f t -> Predicate a f t' -> Predicate a f (t ::: t') infixr 3 Source

Alias of and.

(.|.) :: Predicate a f t -> Predicate a f t -> Predicate a f t infixr 2 Source

Alias of or.

(|||) :: Predicate a f t -> Predicate a f t' -> Predicate a f (Either t t') infixr 2 Source

Alias of orElse.

exec :: Predicate a f t -> a -> (f -> b) -> (t -> b) -> b Source

Result

data Result f t Source

A Bool-like type where each branch--Fail and Okay--carries some metadata.

Constructors

Fail f 
Okay !Double t 

Instances

Monad (Result f) 
Functor (Result f) 
Applicative (Result f) 
(Eq f, Eq t) => Eq (Result f t) 
(Ord f, Ord t) => Ord (Result f t) 
(Show f, Show t) => Show (Result f t) 

result :: (f -> a) -> (Double -> t -> a) -> Result f t -> a Source

newtype ResultT f m t Source

Constructors

ResultT 

Fields

runResultT :: m (Result f t)
 

Instances

MonadTrans (ResultT f) 
Monad m => Monad (ResultT f m) 
Monad m => Functor (ResultT f m) 
Monad m => Applicative (ResultT f m) 
MonadIO m => MonadIO (ResultT f m) 

resultT :: Monad m => (f -> m a) -> (Double -> t -> m a) -> ResultT f m t -> m a Source

resultT' :: Monad m => (f -> m a) -> (t -> m a) -> ResultT f m t -> m a Source

mapResultT :: (m (Result f t) -> n (Result f' t')) -> ResultT f m t -> ResultT f' n t' Source

hoistResult :: Monad m => Result f t -> ResultT f m t Source

okay :: Monad m => Double -> t -> ResultT f m t Source

throwF :: Monad m => f -> ResultT f m t Source

Product

data a ::: b infixr 5 Source

A data-type for combining results of predicate evaluations.

Constructors

a ::: b infixr 5 

Instances

(Eq a, Eq b) => Eq ((:::) a b) 
(Show a, Show b) => Show ((:::) a b) 

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

flip ($) - useful in combination with indexed access, e.g. (x ::: True ::: False)#_2 yields True.

hd :: (a ::: b) -> a Source

tl :: (a ::: b) -> b Source

_1 :: (a ::: b) -> a Source

_2 :: (a ::: (b ::: c)) -> b Source

_3 :: (a ::: (b ::: (c ::: d))) -> c Source

_4 :: (a ::: (b ::: (c ::: (d ::: e)))) -> d Source

_5 :: (a ::: (b ::: (c ::: (d ::: (e ::: f))))) -> e Source

_6 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: g)))))) -> f Source

_7 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: h))))))) -> g Source

_8 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: i)))))))) -> h Source

_9 :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: (i ::: j))))))))) -> i Source

_1' :: (a ::: b) -> a Source

_2' :: (a ::: b) -> b Source

_3' :: (a ::: (b ::: c)) -> c Source

_4' :: (a ::: (b ::: (c ::: d))) -> d Source

_5' :: (a ::: (b ::: (c ::: (d ::: e)))) -> e Source

_6' :: (a ::: (b ::: (c ::: (d ::: (e ::: f))))) -> f Source

_7' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: g)))))) -> g Source

_8' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: h))))))) -> h Source

_9' :: (a ::: (b ::: (c ::: (d ::: (e ::: (f ::: (g ::: (h ::: i)))))))) -> i Source