servant-scotty-0.1.1: Generate a web service for servant 'Resource's using scotty and JSON

Stabilityexperimental
MaintainerAlp Mestanogullari <alp@zalora.com>
Safe HaskellNone

Servant.Scotty

Contents

Description

Module for defining a scotty webservice from Resources.

 EXAMPLE HERE

Synopsis

Setting up handlers for a Resource

class Runnable ops whereSource

Internal class used to drive the recursion on the list of operations when generating all the endpoints and handlers.

This lets everyone care only about the specific behavior of their operations, this class will make sure all the operations of your Resource have an implementation.

Regardless of what's specific about each operation, we just recursively go through all the operations and call runOperation for each of them.

Methods

runResource :: (Functor m, MonadIO m, ScottyError e, Suitables ops a i r) => Resource c a i r e ops -> ScottyT e m ()Source

Call this function to setup a Resource in your scotty application.

Instances

Runnable ([] *)

No operation means we don't setup any handler.

(ScottyOp o, Runnable ops) => Runnable (: * o ops)

Given some already runnable operation list ops, and an operation that we can run in scotty

(that's the ScottyOp o constraint),

we can run the (o ': ops) operation list.

Defining handlers for an operation

class ScottyOp o whereSource

A class that lets you define one or more handler(s) for an operation o.

Associated Types

type Suitable o a i r :: ConstraintSource

Each operation can define its own constraints on:

  • the type of the entries, a * the type by which the entries are indexed, i * the result type r of "effectful" database operations (those that addupdatedelete entries)

This is useful because that way, your types will only have to satisfy the constraints specified by the operations your Resource carries, not some global dumb constraints you have to pay for even if you don't care about the operation that requires this constraint.

Methods

runOperation :: (Functor m, MonadIO m, ScottyError e, Suitable o a i r) => Resource c a i r e (o : ops) -> Operation o c a i r -> ScottyT e m ()Source

Given a Resource and the "database function" (so to speak) corresponding to your operation, do some business in scotty's ScottyT and ActionT monads to define a handler for this very operation.

To provide the "database function" with some Context c you can use withContext to run the operation and context to get the context of your Resource.

To catch exceptions around your db operation in your handler, you can use the excCatcher access the ExceptionCatcher of your Resource and handledWith to catch them and convert them to your error type e. You can then raise the error value if you have a sensible default handler or handle it locally and respond with whatever is appropriate in your case.

Instances

ScottyOp Add

Generate a

 POST /:resourcename

handler for adding entries.

Constraints on @a@, @i@ and @r@:

 type Suitable Add a i r = (FromJSON a, Response (UpdateResponse Add) r)
ScottyOp Delete

Generate a

 DELETE /:resourcename/<index specific stuffs>

handler for deleting entries.

Constraints on @a@, @i@ and @r@:

 type Suitable Delete a i r = (Index i, Response (UpdateResponse Delete) r)
ScottyOp ListAll

Generate a

 GET /:resourcename

handler for listing all entries.

Constraints on @a@, @i@ and @r@:

 type Suitable ListAll a i r = ToJSON a
ScottyOp Update

Generate a

 PUT /:resourcename/<index specific stuffs>

handler for updating an entry.

Constraints on @a@, @i@ and @r@:

 type Suitable Update a i r = (Index i, FromJSON a, Response (UpdateResponse Update) r)
ScottyOp View

Generate a

 GET /:resourcename/<index specific stuffs>

handler for viewing an entry.

Constraints on @a@, @i@ and @r@:

 type Suitable View a i r = (Index i, ToJSON a)

class Index k whereSource

What it means for a scotty Resource to have an index type.

  • idx should lookup in the request path whatever is necessary to get the i of Resource c a i r e ops, for operations that take it as an argument, e.g Delete, Update or View.
  • route should return a String that'll be passed to capture. You may use one or more "path parameters" (calls to param, instances of Param) to compute your value of type k. You probably want to use name on the Resource to generate the beginning of the path.

Methods

idx :: (Functor m, MonadIO m, ScottyError e) => ActionT e m kSource

Lookup the index in the request path

route :: Resource c a k r e ops -> StringSource

String to capture that represents the RoutePattern.

js :: (MonadIO m, ScottyError e, FromJSON a) => ActionT e m aSource

Simply gets the request's body as JSON (or raises an exception if the decoding fails)

safelySource

Arguments

:: (MonadIO m, ScottyError e) 
=> Resource c a i r e ops

the resource, that holds the context c and the exception catchers required to run the operation

-> ActionT e m (c -> IO x)

a scotty action that'll produce the operation we want, with all the arguments but the context already provided.

-> ActionT e m x

returns the result of the operation or raise if an exception the Resource is watching for is thrown, using the appropriate conversion to your application's error type e.

This is a function you'll want to use when defining your own operations.

It runs the second argument to get the operation to run, and feeds it the Resource argument's context and extracts the result.

Intended to be used in runOperation in a way similar to

 -- example: for the 'Delete' operation
 runOperation res op =
   delete (capture $ "/" ++ name res ++ route res) $ do
     result <- safely res $ op <$> idx
     respond result

Here we just take the particular delete operation for the client code's type, lookup the Index argument it takes from the request path and run the operation safely, eventually converting its result to an appropriate response.

class ToJSON resp => Response resp result | result -> resp where

A class that ties return types of your database operations and the output that will be generated to communicate the result.

  • The first type, resp, is the response type that will be encoded in JSON and sent as the response body.
  • The second type, result, is the result type of your "database" or "context" operation.

For example, if you're adding an item, and if you're using postgresql-simple, you'll probably want to use the Response instances defined in the servant-postgresql package, in the Servant.PostgreSQL.Prelude module.

It lets you specify, given a value of your result, if no exception is thrown, what response should be sent as JSON to the client along with what HTTP status.

There's a functional dependency at play: the result type of a database operation determines the representation that'll be picked for generating the json output.

Methods

toResponse :: result -> (resp, Status)

Instances

ToJSON a => Response [a] [a]

Just send the list of entries as a JSON array, with status code 200. Used by ListAll.

ToJSON a => Response (LookupResponse a) (Maybe a)

Make LookupResponse a proper Response for Context lookups returning a Maybe value, returning 404 when Nothing is returned, along with a not found message in json. Used by View.

respond :: (Response resp x, ScottyError e, Monad m) => x -> ActionT e m ()Source

Given the result of some operation, it picks the appropriate response type and uses toResponse to convert the result to a JSON-encodable value along with a status code, both used to then send a response to the client.

Utilities

type family Suitables ops a i r :: ConstraintSource