| Safe Haskell | Safe-Inferred |
|---|
Snap.Predicate.Tutorial
Motivation
The purpose of the snap-predicates package is to facilitate the
convenient definition of safe Snap handlers. Here safety
means that a handler can declare all pre-conditions which must be
fulfilled such that the handler can produce a successful response.
It is then statically guaranteed that the handler will not be
invoked if any of these pre-conditions fails.
Introduction
The snap-predicates package defines a Boolean type
which carries -- in addition to actual truth values T
and F -- meta-data for each case:
dataBooleanf t =F(Maybe f) |TDeltat deriving (Eq, Show)
Delta can in most instances be ignored, i.e. set to 0.
It's purpose is as a measure of distance for those predicates which evaluate
to T but some may be "closer" in some way than others. An
example is for instance HTTP content-negotiations (cf. Accept)
Further there is a type-class Predicate defined which
contains an evaluation function apply, where the
predicate instance is applied to some value, yielding T
or F.
classPredicatep a where typeFValp typeTValp apply :: p -> a ->StateEnv(Boolean (FValp)) (TValp)
All predicates are instances of this type-class, which does not
specify the type against which the predicate is evaluated, nor the types
of actual meta-data for the true/false case of the Boolean returned.
Snap related predicates are normally defined against Request
and in case they fail, they return a status code and an optional message.
Predicates may utilise the stateful Env to cache intermediate
results accross multiple evaluations, i.e. a resource may be declared multiple
times with different sets of predicates which means that in case a predicate
is part of more than one set it is evaluated multiple times for the same
input data. As an optimisation it may be beneficial to store intermediate
results in Env and re-use them later (cf. the implementation
of Accept).
Besides these type definitions, there are some ways to connect two
Predicates to form a new one as the logical OR or the
logical AND of its parts. These are:
Besides evaluating to T or F depending
on the truth values of its parts, these connectives also propagate the
meta-data and Delta appropriately.
If :&: evaluates to T it has to combine
the meta-data of both predicates, and it uses the product type
:*: for this. This type also has a right-associative
data constructor using the same symbol, so one can combine many predicates
without having to nest the meta-data pairs.
In the OR case, the two predicates have potentially meta-data of
different types, so we use a sum type Either whenever we combine
two predicates with :||:. For convenience a type-alias
:+: is defined for Either, which allows simple infix
notation. However, for the common case where both predicates have
meta-data of the same type, there is often no need to distinguish which
OR-branch was true. In this case, the :|: combinator
can be used.
Finally there are Const and Fail to
always evaluate to T or F respectively.
As an example of how these operators are used, see below in section "Routes".
Example Predicate
data Param = ParamByteStringderiving Eq instancePredicateParamRequestwhere typeFValParam =ErrortypeTValParam = ByteString apply (Param x) r = case params r x of [] -> return (F (Error400 (Just $ "Expected parameter '" <> x <> "'."))) (v:_) -> return (T [] v)
This is a simple example looking for the existence of a Request parameter
with the given name. In the success case, the parameter value is returned.
As mentioned before, Snap predicates usually fix the type a from
Predicate above to Request. The associated
types FVal and TVal denote the meta-data
types of the predicate. In this example, the meta-date type is ByteString.
The F-case is Error which contains a status
code and an optional message.
Routes
So how are Predicates used in some Snap application?
One way is to just evaluate them against a given request inside a snap handler, e.g.
someHandler ::Snap() someHandler = do req <-getRequestcaseeval(AcceptApplicationJson:&:Param"baz") req ofT(_:*:bazValue) -> ...F(Just (Errorst msg)) -> ...FNothing -> ...
However another possibility is to augment route definitions with the
Routes monad to use them with route, e.g.
sitemap ::RoutesSnap () sitemap = doget"/a" handlerA $AcceptApplicationJson:&:(Param"name":|:Param"nick"):&:Param"foo"get"/b" handlerB $AcceptTextPlain:&:(Param"name":||:Param"nick"):&:Param"foo"get"/c" handlerC $Fail(Error410 (Just "Gone."))post"/d" handlerD $AcceptApplicationProtobufpost"/e" handlerE $AcceptApplicationXml
The handlers then encode their pre-conditions in their type-signature:
handlerA ::MediaTypeApplicationJson:*:ByteString:*:ByteString -> Snap () handlerB ::MediaTypeTextPlain:*:(ByteString:+:ByteString):*:ByteString -> Snap () handlerC ::MediaTypeApplicationJson:*:Char -> Snap () handlerD ::MediaTypeApplicationProtobuf-> Snap () handlerE ::MediaTypeApplicationXml-> Snap ()
The type-declaration of a handler has to match the corresponding predicate,
i.e. the type of the predicate's T meta-data value:
(MonadSnapm,PredicatepRequest) =>TValp -> m ()
One thing to note is that Fail works with
all T meta-data types which is safe because the handler is never
invoked, or Fail is used in some logical disjunction.
Given the route and handler definitions above, one can then integrate
with Snap via expandRoutes, which turns the
Routes monad into a list of
.
Additionally routes can be turned into Strings via MonadSnap m => [(ByteString, m ())]showRoutes.