Stability | experimental |
---|---|
Maintainer | Alp Mestanogullari <alp@zalora.com> |
Safe Haskell | None |
Instances of ScottyOp
for the operations defined
in Servant.Prelude, along with some reusable types
necessary for the instances.
- module Servant.Prelude
- module Servant.Response.Prelude
- class ScottyOp o where
- type Suitable o a i r :: Constraint
- 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 ()
- module Servant.Scotty.Arguments
- module Servant.Scotty.Response
- module Web.Scotty.Trans
Defining Resource
s and standard operations
module Servant.Prelude
Standard response types
module Servant.Response.Prelude
ScottyOp
class and standard operations implementations in scotty
A class that lets you define one or more handler(s) for an operation o
.
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 typer
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.
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.
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) |
Helpful types, functions, classes and instances
module Servant.Scotty.Arguments
module Servant.Scotty.Response
module Web.Scotty.Trans