snap-predicates-0.3.1: Declarative routing for Snap.

Safe HaskellSafe-Inferred

Data.Predicate

Synopsis

Documentation

type Delta = DoubleSource

Delta is a measure of distance. It is (optionally) used in predicates that evaluate to T but not uniquely so, i.e. different evaluations of T are possible and they may have a different "fitness".

An example is content-negotiation. A HTTP request may specify a preference list of various media-types. A predicate matching one specific media-type evaluates to T, but other media-types may match even better. To represent this ambivalence, the predicate will include a delta value which can be used to decide which of the matching predicates should be preferred.

data Boolean f t Source

A Bool-like type where each branch True or False carries some meta-data which is threaded through Predicate evaluation.

Constructors

F f

logical False with some meta-data

T Delta t

logical True with some meta-data

Instances

(Eq f, Eq t) => Eq (Boolean f t) 
(Show f, Show t) => Show (Boolean f t) 

class Predicate p a whereSource

The Predicate class declares the function apply which evaluates the predicate against some value, returning a value of type Boolean. Besides being parameterised over predicate type and predicate parameter, the class is also parameterised over the actual types of T's and F's meta-data.

Associated Types

type FVal p Source

type TVal p Source

Methods

apply :: p -> a -> State Env (Boolean (FVal p) (TVal p))Source

data Const f t whereSource

A Predicate instance which always returns T with the given value as T's meta-data.

Constructors

Const :: t -> Const f t 

Instances

Show t => Show (Const f t) 
Predicate (Const f t) a 

data Fail f t whereSource

A Predicate instance which always returns F with the given value as F's meta-data.

Constructors

Fail :: f -> Fail f t 

Instances

Show f => Show (Fail f t) 
Predicate (Fail f t) a 

data a :|: b Source

A Predicate instance corresponding to the logical OR connective of two Predicates. It requires the meta-data of each True branch to be of the same type.

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

Constructors

a :|: b 

Instances

(Show a, Show b) => Show (:|: a b) 
(Predicate a c, Predicate b c, ~ * (TVal a) (TVal b), ~ * (FVal a) (FVal b)) => Predicate (:|: a b) c 

type :+: a b = Either a bSource

data a :||: b Source

A Predicate instance corresponding to the logical OR connective of two Predicates. The meta-data of each True branch can be of different types.

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

Constructors

a :||: b 

Instances

(Show a, Show b) => Show (:||: a b) 
(Predicate a c, Predicate b c, ~ * (FVal a) (FVal b)) => Predicate (:||: a b) c 

data a :*: b Source

Data-type used for tupling-up the results of :&:.

Constructors

a :*: b 

Instances

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

data a :&: b Source

A Predicate instance corresponding to the logical AND connective of two Predicates.

Constructors

a :&: b 

Instances

(Show a, Show b) => Show (:&: a b) 
(Predicate a c, Predicate b c, ~ * (FVal a) (FVal b)) => Predicate (:&: a b) c 

eval :: Predicate p a => p -> a -> Boolean (FVal p) (TVal p)Source

Evaluate the given predicate p against the given value a.

with :: (Monad m, Predicate p a) => p -> a -> (TVal p -> m ()) -> m ()Source

The with function will invoke the given function only if the predicate p applied to the test value a evaluates to T.