servant-0.1: A library to generate REST-style webservices on top of scotty, handling all the boilerplate for you

Stabilityexperimental
MaintainerAlp Mestanogullari <alp@zalora.com>
Safe HaskellSafe-Inferred

Servant.Resource

Description

Defining Resources.

Synopsis

Documentation

data Resource c a i r e ops Source

A resource that:

  • uses some context type c (think database connection) * manages entries of type a * (optionally) supports indexing through the i type (a dumb ID, or something like data FooId = ByToken Token | ByID Integer). That can be useful when trying to view, update or delete a particular entry, for example. * uses r as the return type (tagged by the operation type) for effectful database operations (e.g. adding, updating, deleting entries for example). * can catch exceptions, converting them to some error type e of yours * supports the operations listed in the ops type list. a corresponding (heterogeneous) list of database functions is held internally and we ask the compiler to make the types of these functions match with the ones expected for the operations listed at the type-level.

Instances

(Show o, Show (Resource c a i r e ops)) => Show (Resource c a i r e (: * o ops)) 
Show (Resource c a i r e ([] *)) 

name :: Resource c a i r e ops -> StringSource

Get the name of the Resource

context :: Resource c a i r e ops -> Context cSource

Gives the Context attached to this Resource

excCatcher :: Resource c a i r e ops -> ExceptionCatcher eSource

Hands you the ExceptionCatcher you can handledWith with to make your "database operations" exception safe.

withHeadOperation :: Resource c a i r e (o : ops) -> (Resource c a i r e (o : ops) -> Operation o c a i r -> b) -> bSource

Typically, functions that will use our operations will need access to the resource's name and what not, so we need to provide them with the resource. But we obviously also need the "database function" associated to our operation. So we provide it too.

Just give this function a Resource and a function that uses it, most likely to run the handler for an operation, and it'll give your function the right arguments.

dropHeadOperation :: Resource c a i r e (o : ops) -> Resource c a i r e opsSource

Type-safely "unconsider" the first operation in the list

Helpful when performing recursion on the type-level list and the internal list of "database functions" simultaneously.

mkResource :: String -> Context c -> ExceptionCatcher e -> Resource c a i r e `[]`Source

Create an empty resource that doesn't support any operation and catches exceptions using the given ExceptionCatcher. Any operation supported later on can make use of the provided Context, by simply doing:

 withContext (context resource) $ \c -> ...

where c could be a PostgreSQL connection, for example.

addOperation :: Contains o ops ~ False => Operation o c a i r -> Resource c a i r e ops -> Resource c a i r e (o : ops)Source

Add an operation to a resource by specifying the "database function" that'll actually perform the lookup, update, listing, search and what not.

We statically enforce that the operation we're adding isn't already supported by the Resource, when built with ghc >= 7.8.

type family Operation o c a i r :: *Source

Map an operation tag o to some combination of the other type parameters.

For instance, if we look at Add, we know that we'll need our "connection type" c and a value to add, of type a. The result will be of type IO (r Add). If we put this all together, we get:

 type instance Operation Add c a i r = a -> c -> IO (r Add)

Whereas for listing all entries (ListAll), we just want some kind of connection c and we get back [a].

 type instance Operation ListAll c a i r = c -> IO [a]

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

Reversed function application.

 x & f = f x

type family Ops ops c a i r :: [*]Source

Type level map-like function that replaces an operation's tag by the type of the associated "database function"

For example:

 Ops [Add, List] c a i r

will result in:

 [ a -> c -> IO r -- what 'Add' is replaced by
 , c -> IO [a]    -- what 'List' is replaced by
 ]

This is useful as we can exactly determine the type of the heterogeneous list that holds the actual "dtabase functions" that will perform the operations, using Ops. This among other things enforces a strong correspondance between the type-level list of operations and the (heterogeneous) list of functions held in the Resource we're interested in.

That means we can't magically convert a Resource into one that supports one more operations without registering a function for it (which must have the right type, or your code won't compile.

type Contains elem list = FalseSource

Utility (closed) type family to detect whether a type is contained in a type-level list of types