wai-predicates-0.5: WAI request predicates

Safe HaskellSafe-Inferred

Data.Predicate

Contents

Synopsis

Predicate

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

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 tSource

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

failure :: f -> Predicate a f tSource

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 tSource

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')Source

Alias of and.

(.|.) :: Predicate a f t -> Predicate a f t -> Predicate a f tSource

Alias of or.

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

Alias of orElse.

opt :: Predicate a f t -> Predicate a f (Maybe t)Source

A predicate modifier which makes the given predicate optional, i.e. the Okay metadata type becomes a Maybe and in the failure-case Nothing is returned.

def :: t -> Predicate a f t -> Predicate a f tSource

A predicate modifier which returns as Okay metadata the provided default value if the given predicate fails.

mapOkay :: (t -> Result f t') -> Predicate a f t -> Predicate a f t'Source

Like fmap, but only maps the Okay metadata to another result.

mapFail :: (f -> Result f' t) -> Predicate a f t -> Predicate a f' tSource

Like mapOkay, but for the Fail case.

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

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 -> aSource

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 aSource

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

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 tSource

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

throwF :: Monad m => f -> ResultT f m tSource

Product

data a ::: b Source

A data-type for combining results of predicate evaluations.

Constructors

a ::: b 

Instances

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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