snap-predicates-0.1.0: Predicates for route definitions.

Safe HaskellSafe-Inferred

Snap.Predicates.Tutorial

Contents

Synopsis

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:

data Boolean f t =
    F (Maybe f)
  | T t
  deriving (Eq, Show)

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.

class Predicate p a where
    type FVal p
    type TVal p
    apply :: p -> a -> Boolean (FVal p) (TVal p)

All concrete 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.

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 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 Routes section.

Example Predicate

data Accept = Accept ByteString deriving Eq

instance Predicate Accept Request where
    type FVal Accept = (Word, Maybe ByteString)
    type TVal Accept = ()
    apply (Accept x) r =
        if x `elem` headerValues r "Accept"
            then T ()
            else F $ Just (406, Just $ "Expected 'Accept: "  x  "'.")

This is a simple example testing the value of a Requests accept header against some given value. The function headerValues is not shown, but gets the actual Accept-Header values of the request.

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, there is no useful information for the T-case, so TVal becomes '()'. The F-case is set to the pair (Word, Maybe ByteString) and indeed, if the predicate fails it sets the right HTTP status code (406) and some helpful message.

Routes

So how are Predicates used in some Snap application? One way is to just apply them to a given request inside a snap handler, e.g.

someHandler :: Snap ()
someHandler = do
    req <- getRequest
    case apply (Accept "application/json" :&: Param "baz") req of
        T (_ :*: bazValue) -> ...
        F (Just (i, msg))  -> ...
        F Nothing          -> ...

However another possibility is to augment route definitions with the Routes monad to use them with route, e.g.

sitemap :: Routes Snap ()
sitemap = do
    get  "/a" handlerA $ AcceptJson :&: (Param "name" :|: Param "nick") :&: Param "foo"
    get  "/b" handlerB $ AcceptJson :&: (Param "name" :||: Param "nick") :&: Param "foo"
    get  "/c" handlerC $ Fail (410, Just "Gone.")
    post "/d" handlerD $ AcceptThrift
    post "/e" handlerE $ Accept "plain/text"

The handlers then encode their pre-conditions in their type-signature:

handlerA :: AcceptJson :*: ByteString :*: ByteString -> Snap ()
handlerB :: AcceptJson :*: (ByteString :+: ByteString) :*: ByteString -> Snap ()
handlerC :: AcceptJson :*: Char -> Snap ()
handlerD :: AcceptThrift -> Snap ()
handlerE :: () -> Snap ()

As usually these type-declarations have to match, or else the code will not compile. One thing to note is that Fail works with all handler signatures, which is safe, because the handler is never invoked, or else 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 MonadSnap m => [(ByteString, m ())]. Additionally routes can be turned into Strings via showRoutes.