| Safe Haskell | None |
|---|
Snap.Snaplet.Rest
- serveResource :: (HasResourceConfig b, FromRequest id) => Resource res (Handler b b) id diff -> Handler b b ()
- serveResourceWith :: (MonadSnap m, FromRequest id) => Resource res m id diff -> ResourceConfig m -> m ()
- data Resource res m id diff
- resource :: Resource res m id diff
- addMedia :: Monad m => Media res m diff int -> ResourceBuilder res m id diff
- setCreate :: (res -> m ()) -> ResourceBuilder res m id diff
- setRead :: (id -> m [res]) -> ResourceBuilder res m id diff
- setUpdate :: (id -> diff -> m Bool) -> ResourceBuilder res m id diff
- setDelete :: (id -> m Bool) -> ResourceBuilder res m id diff
- setToDiff :: (res -> diff) -> ResourceBuilder res m id diff
- setFromParams :: (Params -> Maybe id) -> ResourceBuilder res m id diff
- setPutAction :: PutAction -> ResourceBuilder res m id diff
- data PutAction
- class FromRequest id where
- fromPath :: ByteString -> Maybe id
- parseRead :: Read a => ByteString -> Maybe a
- type Params = Map ByteString [ByteString]
- data Media res m diff int
- newMedia :: (Intermediate int, MonadSnap m) => [MediaType] -> [MediaType] -> Media res m diff int
- newIntermediateMedia :: (int -> m ByteString) -> (ByteString -> m (Maybe int)) -> [MediaType] -> [MediaType] -> Media res m diff int
- newRequestMedia :: (ByteString -> m (Maybe int)) -> [MediaType] -> Media res m diff int
- newResponseMedia :: (int -> m ByteString) -> [MediaType] -> Media res m diff int
- type MediaSetter res m diff int f a = Setter (Media res m diff int) (Media res m diff int) (f a) a
- fromResource :: MediaSetter res m diff int Maybe (res -> m int)
- toResource :: MediaSetter res m diff int Maybe (int -> m (Maybe res))
- toDiff :: MediaSetter res m diff int Maybe (int -> m (Maybe diff))
- toEither :: MediaSetter res m res int Both (int -> m (Maybe res))
- fromResourceList :: MediaSetter res m diff int Maybe ([res] -> m int)
- toResourceList :: MediaSetter res m diff int Maybe (int -> m (Maybe [res]))
- json :: Monad m => Media res m diff Value
- jsonFromInstances :: (Monad m, ToJSON res, FromJSON res, FromJSON diff) => Media res m diff Value
- xml :: Monad m => Media res m diff Document
- xhtml :: MonadSnap m => Media res m diff ByteString
- html :: MonadSnap m => Media res m diff ByteString
- form :: MonadSnap m => Media res m diff Params
- multipart :: MonadSnap m => Media res m diff ByteString
- data ResourceConfig m = ResourceConfig {
- readLimit :: Maybe Int
- maxRequestBodySize :: Int64
- onHeaderFailure :: m ()
- onPathFailure :: m ()
- onQueryFailure :: m ()
- onLookupFailure :: m ()
- onMethodFailure :: m ()
- onAcceptFailure :: m ()
- onContentTypeFailure :: m ()
- onContentParseFailure :: m ()
- defaultConfig :: MonadSnap m => Int64 -> ResourceConfig m
- class HasResourceConfig b where
- resourceLens :: SnapletLens (Snaplet b) (ResourceConfig (Handler b b))
- type Resources b = ResourceConfig (Handler b b)
- resourceInit :: ResourceConfig (Handler b b) -> SnapletInit b (Resources b)
- resourceInitDefault :: Int64 -> SnapletInit b (Resources b)
Serving resources
serveResource :: (HasResourceConfig b, FromRequest id) => Resource res (Handler b b) id diff -> Handler b b ()Source
Serve the specified resource using the configuration in the monad.
serveResourceWith :: (MonadSnap m, FromRequest id) => Resource res m id diff -> ResourceConfig m -> m ()Source
Serve the specified resource using the given configuration.
Resource
data Resource res m id diff Source
A resource descriptor for the type res. The resource runs in the monad
m, identifies resources with values of the type id, and describes
changes with value of the type diff.
resource :: Resource res m id diffSource
The empty resource descriptor, useful as a starting point for building resources.
addMedia :: Monad m => Media res m diff int -> ResourceBuilder res m id diffSource
Add a media representation for rendering and parsing.
setCreate :: (res -> m ()) -> ResourceBuilder res m id diffSource
Set the create method for the resource.
setRead :: (id -> m [res]) -> ResourceBuilder res m id diffSource
Set the read method for the resource.
setUpdate :: (id -> diff -> m Bool) -> ResourceBuilder res m id diffSource
Set the update method for the resource. The method must return a boolean, indicating whether anything was updated.
setDelete :: (id -> m Bool) -> ResourceBuilder res m id diffSource
Set the delete method for the resource. The method must return a boolean, indicating whether anything was deleted.
setToDiff :: (res -> diff) -> ResourceBuilder res m id diffSource
Sets the conversion function from resource to diff value.
setFromParams :: (Params -> Maybe id) -> ResourceBuilder res m id diffSource
Sets the URL query string parser.
setPutAction :: PutAction -> ResourceBuilder res m id diffSource
Sets a specific action to take when a PUT method is received. If not set, this defaults to trying to update and then creating if that fails.
Indicates which action that a PUT request should take for a resource.
Request parsing
class FromRequest id whereSource
Instances of this class can be parsed from the remaining path information at the current route, and potentially also the URL parameters.
Methods
fromPath :: ByteString -> Maybe idSource
Parse a value from the remaining path information. A value of
Nothing indicates that the parse failed.
Instances
| FromRequest Int | |
| FromRequest () | |
| FromRequest a => FromRequest [a] | |
| FromRequest a => FromRequest (Maybe a) | |
| FromRequest (CI String) | |
| FromRequest (CI ByteString) | |
| FromRequest (CI ByteString) | |
| FromRequest (CI Text) | |
| FromRequest a => FromRequest (Either a b) | |
| (FromRequest a, FromRequest b) => FromRequest (a, b) | |
| (FromRequest a, FromRequest b, FromRequest c) => FromRequest (a, b, c) | |
| (FromRequest a, FromRequest b, FromRequest c, FromRequest d) => FromRequest (a, b, c, d) |
parseRead :: Read a => ByteString -> Maybe aSource
A convenient helper function that wraps a read failure into Nothing
instead of throwing an error.
type Params = Map ByteString [ByteString]
A type alias for the HTTP parameters mapping. Each parameter
key maps to a list of ByteString values; if a parameter is specified
multiple times (e.g.: "GET /foo?param=bar1¶m=bar2"), looking up
"param" in the mapping will give you ["bar1", "bar2"].
Media
data Media res m diff int Source
A grouping of mediatypes and their associated renderers and parsers. You can use the standard instances defined below, or define your own.
newMedia :: (Intermediate int, MonadSnap m) => [MediaType] -> [MediaType] -> Media res m diff intSource
Construct a new media grouping with the given response and request mediatypes.
newIntermediateMedia :: (int -> m ByteString) -> (ByteString -> m (Maybe int)) -> [MediaType] -> [MediaType] -> Media res m diff intSource
Construct a new media grouping with an intermediate type between the resource and the rendered form.
newRequestMedia :: (ByteString -> m (Maybe int)) -> [MediaType] -> Media res m diff intSource
Construct a new media grouping with request mediatypes only.
newResponseMedia :: (int -> m ByteString) -> [MediaType] -> Media res m diff intSource
Construct a new media grouping with response mediatypes only.
type MediaSetter res m diff int f a = Setter (Media res m diff int) (Media res m diff int) (f a) aSource
A Setter for defining properties of a media grouping.
fromResource :: MediaSetter res m diff int Maybe (res -> m int)Source
Set the resource renderer.
toResource :: MediaSetter res m diff int Maybe (int -> m (Maybe res))Source
Set the resource parser.
toDiff :: MediaSetter res m diff int Maybe (int -> m (Maybe diff))Source
Set the diff parser.
toEither :: MediaSetter res m res int Both (int -> m (Maybe res))Source
Set the resource and diff parser at the same time.
fromResourceList :: MediaSetter res m diff int Maybe ([res] -> m int)Source
Set the resource list renderer.
toResourceList :: MediaSetter res m diff int Maybe (int -> m (Maybe [res]))Source
Set the resource list parser.
Common media instances
json :: Monad m => Media res m diff ValueSource
Outputs JSON in UTF-8 and parses JSON agnostic of character set.
jsonFromInstances :: (Monad m, ToJSON res, FromJSON res, FromJSON diff) => Media res m diff ValueSource
Outputs JSON in UTF-8 and parses JSON agnostic of character set. Uses the type class instances to automatically set the media methods.
xml :: Monad m => Media res m diff DocumentSource
Outputs XML in UTF-8 and parses XML agnostic of character set.
xhtml :: MonadSnap m => Media res m diff ByteStringSource
Supports both XHTML and HTML in UTF-8 as the output format only.
Recommended over html if the output will be valid XHTML.
html :: MonadSnap m => Media res m diff ByteStringSource
Supports HTML in UTF-8 as the output format only. Use xhtml if the
output is guaranteed to be well formed.
form :: MonadSnap m => Media res m diff ParamsSource
Supports URL-encoded web forms as the input format only.
multipart :: MonadSnap m => Media res m diff ByteStringSource
Supports multipart web forms as the input format only.
Config
data ResourceConfig m Source
Configuration data.
Constructors
| ResourceConfig | |
Fields
| |
defaultConfig :: MonadSnap m => Int64 -> ResourceConfig mSource
The default configuration settings. Requires a value for the maximum size of a request body.
defaultConfig mrbs = ResourceConfig
{ readLimit = Nothing
, maxRequestBodySize = mrbs
, on*Failure = write "reason"
}
class HasResourceConfig b whereSource
The type class for an implementing Snaplet.
Methods
resourceLens :: SnapletLens (Snaplet b) (ResourceConfig (Handler b b))Source
Retrieve the configuration from the Snaplet monad.
type Resources b = ResourceConfig (Handler b b)Source
Convenience alias of ResourceConfig.
resourceInit :: ResourceConfig (Handler b b) -> SnapletInit b (Resources b)Source
Initialize the resource snaplet with the given configuration.
resourceInitDefault :: Int64 -> SnapletInit b (Resources b)Source
Initialize the resource snaplet with the default configuration.