| Safe Haskell | Safe-Inferred |
|---|
Data.Predicate
- type Delta = Double
- data Boolean f t
- class Predicate p a where
- data Const f t where
- data Fail f t where
- data a :|: b = a :|: b
- type :+: a b = Either a b
- data a :||: b = a :||: b
- data a :*: b = a :*: b
- data a :&: b = a :&: b
- eval :: Predicate p a => p -> a -> Boolean (FVal p) (TVal p)
- with :: (Monad m, Predicate p a) => p -> a -> (TVal p -> m ()) -> m ()
Documentation
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.
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.
Instances
| (Typeable a, Readable a) => Predicate (ParamDef a) Request | |
| (Typeable a, Readable a) => Predicate (ParamOpt a) Request | |
| (Typeable a, Readable a) => Predicate (Param a) Request | |
| Typeable a => Predicate (Parameter a) Request | |
| (Predicate a c, Predicate b c, ~ * (FVal a) (FVal b)) => Predicate (:&: a b) c | |
| (Predicate a c, Predicate b c, ~ * (FVal a) (FVal b)) => Predicate (:||: a b) c | |
| (Predicate a c, Predicate b c, ~ * (TVal a) (TVal b), ~ * (FVal a) (FVal b)) => Predicate (:|: a b) c | |
| Predicate (Fail f t) a | |
| Predicate (Const f t) a | |
| (MType t, MSubType s) => Predicate (Accept t s) Request | |
| (MType t, MSubType s) => Predicate (ContentType t s) Request |
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 |
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 |
Constructors
| a :&: b |