| Safe Haskell | None | 
|---|
Snap.Core
Contents
Description
This module contains the core type definitions, class instances, and functions
for HTTP as well as the Snap monad, which is used for web handlers.
- data Snap a
- runSnap :: Snap a -> (ByteString -> IO ()) -> ((Int -> Int) -> IO ()) -> Request -> Iteratee ByteString IO (Request, Response)
- class (Monad m, MonadIO m, MonadCatchIO m, MonadPlus m, Functor m, Applicative m, Alternative m) => MonadSnap m where
- data NoHandlerException = NoHandlerException String
- bracketSnap :: IO a -> (a -> IO b) -> (a -> Snap c) -> Snap c
- finishWith :: MonadSnap m => Response -> m a
- catchFinishWith :: Snap a -> Snap (Either Response a)
- pass :: MonadSnap m => m a
- terminateConnection :: (Exception e, MonadCatchIO m) => e -> m a
- type EscapeHttpHandler = ((Int -> Int) -> IO ()) -> Iteratee ByteString IO () -> Iteratee ByteString IO ()
- escapeHttp :: MonadCatchIO m => EscapeHttpHandler -> m ()
- method :: MonadSnap m => Method -> m a -> m a
- methods :: MonadSnap m => [Method] -> m a -> m a
- path :: MonadSnap m => ByteString -> m a -> m a
- pathArg :: (Readable a, MonadSnap m) => (a -> m b) -> m b
- dir :: MonadSnap m => ByteString -> m a -> m a
- ifTop :: MonadSnap m => m a -> m a
- route :: MonadSnap m => [(ByteString, m a)] -> m a
- routeLocal :: MonadSnap m => [(ByteString, m a)] -> m a
- getRequest :: MonadSnap m => m Request
- getsRequest :: MonadSnap m => (Request -> a) -> m a
- getResponse :: MonadSnap m => m Response
- getsResponse :: MonadSnap m => (Response -> a) -> m a
- putRequest :: MonadSnap m => Request -> m ()
- putResponse :: MonadSnap m => Response -> m ()
- modifyRequest :: MonadSnap m => (Request -> Request) -> m ()
- modifyResponse :: MonadSnap m => (Response -> Response) -> m ()
- localRequest :: MonadSnap m => (Request -> Request) -> m a -> m a
- withRequest :: MonadSnap m => (Request -> m a) -> m a
- withResponse :: MonadSnap m => (Response -> m a) -> m a
- logError :: MonadSnap m => ByteString -> m ()
- runRequestBody :: MonadSnap m => Iteratee ByteString IO a -> m a
- getRequestBody :: MonadSnap m => m ByteString
- readRequestBody :: MonadSnap m => Int64 -> m ByteString
- transformRequestBody :: (forall a. Enumerator Builder IO a) -> Snap ()
- data Request
- data Response
- data Headers
- class  HasHeaders a  where- updateHeaders :: (Headers -> Headers) -> a -> a
- headers :: a -> Headers
 
- type Params = Map ByteString [ByteString]
- data Method
- data  Cookie  = Cookie {- cookieName :: !ByteString
- cookieValue :: !ByteString
- cookieExpires :: !(Maybe UTCTime)
- cookieDomain :: !(Maybe ByteString)
- cookiePath :: !(Maybe ByteString)
- cookieSecure :: !Bool
- cookieHttpOnly :: !Bool
 
- type HttpVersion = (Int, Int)
- addHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a
- setHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> a
- getHeader :: HasHeaders a => CI ByteString -> a -> Maybe ByteString
- getHeaders :: HasHeaders a => CI ByteString -> a -> Maybe [ByteString]
- listHeaders :: HasHeaders a => a -> [(CI ByteString, ByteString)]
- deleteHeader :: HasHeaders a => CI ByteString -> a -> a
- ipHeaderFilter :: MonadSnap m => m ()
- ipHeaderFilter' :: MonadSnap m => CI ByteString -> m ()
- rqServerName :: Request -> ByteString
- rqServerPort :: Request -> Int
- rqRemoteAddr :: Request -> ByteString
- rqRemotePort :: Request -> Int
- rqLocalAddr :: Request -> ByteString
- rqLocalHostname :: Request -> ByteString
- rqIsSecure :: Request -> Bool
- rqContentLength :: Request -> Maybe Int
- rqMethod :: Request -> Method
- rqVersion :: Request -> HttpVersion
- rqCookies :: Request -> [Cookie]
- rqPathInfo :: Request -> ByteString
- rqContextPath :: Request -> ByteString
- rqURI :: Request -> ByteString
- rqQueryString :: Request -> ByteString
- rqParams :: Request -> Params
- rqQueryParams :: Request -> Params
- rqPostParams :: Request -> Params
- rqParam :: ByteString -> Request -> Maybe [ByteString]
- rqPostParam :: ByteString -> Request -> Maybe [ByteString]
- rqQueryParam :: ByteString -> Request -> Maybe [ByteString]
- getParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getPostParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getQueryParam :: MonadSnap m => ByteString -> m (Maybe ByteString)
- getParams :: MonadSnap m => m Params
- getPostParams :: MonadSnap m => m Params
- getQueryParams :: MonadSnap m => m Params
- rqModifyParams :: (Params -> Params) -> Request -> Request
- rqSetParam :: ByteString -> [ByteString] -> Request -> Request
- emptyResponse :: Response
- setResponseCode :: Int -> Response -> Response
- setResponseStatus :: Int -> ByteString -> Response -> Response
- rspStatus :: Response -> Int
- rspStatusReason :: Response -> ByteString
- setContentType :: ByteString -> Response -> Response
- addResponseCookie :: Cookie -> Response -> Response
- getResponseCookie :: ByteString -> Response -> Maybe Cookie
- getResponseCookies :: Response -> [Cookie]
- deleteResponseCookie :: ByteString -> Response -> Response
- modifyResponseCookie :: ByteString -> (Cookie -> Cookie) -> Response -> Response
- expireCookie :: MonadSnap m => ByteString -> Maybe ByteString -> m ()
- getCookie :: MonadSnap m => ByteString -> m (Maybe Cookie)
- readCookie :: (MonadSnap m, Readable a) => ByteString -> m a
- setContentLength :: Int64 -> Response -> Response
- clearContentLength :: Response -> Response
- redirect :: MonadSnap m => ByteString -> m a
- redirect' :: MonadSnap m => ByteString -> Int -> m a
- setBufferingMode :: Bool -> Response -> Response
- getBufferingMode :: Response -> Bool
- setResponseBody :: (forall a. Enumerator Builder IO a) -> Response -> Response
- modifyResponseBody :: (forall a. Enumerator Builder IO a -> Enumerator Builder IO a) -> Response -> Response
- addToOutput :: MonadSnap m => (forall a. Enumerator Builder IO a) -> m ()
- writeBuilder :: MonadSnap m => Builder -> m ()
- writeBS :: MonadSnap m => ByteString -> m ()
- writeLazyText :: MonadSnap m => Text -> m ()
- writeText :: MonadSnap m => Text -> m ()
- writeLBS :: MonadSnap m => ByteString -> m ()
- sendFile :: MonadSnap m => FilePath -> m ()
- sendFilePartial :: MonadSnap m => FilePath -> (Int64, Int64) -> m ()
- setTimeout :: MonadSnap m => Int -> m ()
- extendTimeout :: MonadSnap m => Int -> m ()
- modifyTimeout :: MonadSnap m => (Int -> Int) -> m ()
- getTimeoutAction :: MonadSnap m => m (Int -> IO ())
- getTimeoutModifier :: MonadSnap m => m ((Int -> Int) -> IO ())
- type Enumerator a m b = Step a m b -> Iteratee a m b
- newtype SomeEnumerator = SomeEnumerator (forall a. Enumerator ByteString IO a)
- formatHttpTime :: CTime -> IO ByteString
- parseHttpTime :: ByteString -> IO CTime
- parseUrlEncoded :: ByteString -> Map ByteString [ByteString]
- buildUrlEncoded :: Map ByteString [ByteString] -> Builder
- printUrlEncoded :: Map ByteString [ByteString] -> ByteString
- urlEncode :: ByteString -> ByteString
- urlEncodeBuilder :: ByteString -> Builder
- urlDecode :: ByteString -> Maybe ByteString
The Snap Monad
runSnap :: Snap a -> (ByteString -> IO ()) -> ((Int -> Int) -> IO ()) -> Request -> Iteratee ByteString IO (Request, Response)Source
Runs a Snap monad action in the 'Iteratee IO' monad.
class (Monad m, MonadIO m, MonadCatchIO m, MonadPlus m, Functor m, Applicative m, Alternative m) => MonadSnap m whereSource
Snap is the Monad that user web handlers run in. Snap gives you:
-  stateful access to fetch or modify an HTTP Request
-  stateful access to fetch or modify an HTTP Response
-  failure / Alternative/MonadPlussemantics: aSnaphandler can choose not to handle a given request, usingemptyor its synonympass, and you can try alternative handlers with the<|>operator:
a :: Snap String a = pass b :: Snap String b = return "foo" c :: Snap String c = a <|> b -- try running a, if it fails then try b
-  convenience functions (writeBS,writeLBS,writeText,writeLazyText,addToOutput) for queueing output to be written to theResponse:
 a :: (forall a . Enumerator a) -> Snap ()
 a someEnumerator = do
     writeBS "I'm a strict bytestring"
     writeLBS "I'm a lazy bytestring"
     writeText "I'm strict text"
     addToOutput someEnumerator
-  early termination: if you call finishWith:
a :: Snap () a = do modifyResponse $ setResponseStatus 500 "Internal Server Error" writeBS "500 error" r <- getResponse finishWith r
then any subsequent processing will be skipped and supplied Response
   value will be returned from runSnap as-is.
a :: Snap () a = liftIO fireTheMissiles
-  the ability to set or extend a timeout which will kill the handler thread
   after Nseconds of inactivity (the default is 20 seconds):
a :: Snap () a = setTimeout 30
-  throw and catch exceptions using a MonadCatchIOinstance:
 foo :: Snap ()
 foo = bar `catch` \(e::SomeException) -> baz
   where
     bar = throw FooException
- log a message to the error log:
foo :: Snap () foo = logError "grumble."
You may notice that most of the type signatures in this module contain a
(MonadSnap m) => ... typeclass constraint. MonadSnap is a typeclass which,
in essence, says "you can get back to the Snap monad from here". Using
MonadSnap you can extend the Snap monad with additional functionality and
still have access to most of the Snap functions without writing lift
everywhere. Instances are already provided for most of the common monad
transformers (ReaderT, WriterT, StateT, etc.).
MonadSnap is a type class, analogous to MonadIO for IO, that makes
 it easy to wrap Snap inside monad transformers.
Instances
| MonadSnap Snap | |
| MonadSnap m => MonadSnap (ListT m) | |
| MonadSnap m => MonadSnap (ContT c m) | |
| (MonadSnap m, Error e) => MonadSnap (ErrorT e m) | |
| MonadSnap m => MonadSnap (ReaderT r m) | |
| MonadSnap m => MonadSnap (StateT s m) | |
| MonadSnap m => MonadSnap (StateT s m) | |
| (MonadSnap m, Monoid w) => MonadSnap (WriterT w m) | |
| (MonadSnap m, Monoid w) => MonadSnap (WriterT w m) | |
| (MonadSnap m, Monoid w) => MonadSnap (RWST r w s m) | |
| (MonadSnap m, Monoid w) => MonadSnap (RWST r w s m) | 
data NoHandlerException Source
This exception is thrown if the handler you supply to runSnap fails.
Constructors
| NoHandlerException String | 
Functions for control flow and early termination
bracketSnap :: IO a -> (a -> IO b) -> (a -> Snap c) -> Snap cSource
This function brackets a Snap action in resource acquisition and
 release. This is provided because MonadCatchIO's bracket function
 doesn't work properly in the case of a short-circuit return from
 the action being bracketed.
In order to prevent confusion regarding the effects of the aquisition and release actions on the Snap state, this function doesn't accept Snap actions for the acquire or release actions.
This function will run the release action in all cases where the acquire action succeeded. This includes the following behaviors from the bracketed Snap action.
- Normal completion
-  Short-circuit completion, either from calling failorfinishWith
- An exception being thrown.
finishWith :: MonadSnap m => Response -> m aSource
catchFinishWith :: Snap a -> Snap (Either Response a)Source
Capture the flow of control in case a handler calls finishWith.
WARNING: in the event of a call to transformRequestBody it is possible
 to violate HTTP protocol safety when using this function. If you call
 catchFinishWith it is suggested that you do not modify the body of the
 Response which was passed to the finishWith call.
pass :: MonadSnap m => m aSource
Fails out of a Snap monad action.  This is used to indicate
 that you choose not to handle the given request within the given
 handler.
terminateConnection :: (Exception e, MonadCatchIO m) => e -> m aSource
Terminate the HTTP session with the given exception.
Escaping HTTP
escapeHttp :: MonadCatchIO m => EscapeHttpHandler -> m ()Source
Terminate the HTTP session and hand control to some external handler, escaping all further HTTP traffic.
The external handler takes two arguments: a function to modify the thread's timeout, and a write end to the socket.
Routing
method :: MonadSnap m => Method -> m a -> m aSource
Runs a Snap monad action only if the request's HTTP method matches
 the given method.
methods :: MonadSnap m => [Method] -> m a -> m aSource
Runs a Snap monad action only if the request's HTTP method matches
 one of the given methods.
Arguments
| :: MonadSnap m | |
| => ByteString | path to match against | 
| -> m a | handler to run | 
| -> m a | 
Runs a Snap monad action only for requests where rqPathInfo is
 exactly equal to the given string. If the path matches, locally sets
 rqContextPath to the old value of rqPathInfo, sets rqPathInfo="",
 and runs the given handler.
pathArg :: (Readable a, MonadSnap m) => (a -> m b) -> m bSource
Runs a Snap monad action only when the first path component is
 successfully parsed as the argument to the supplied handler function.
Arguments
| :: MonadSnap m | |
| => ByteString | path component to match | 
| -> m a | handler to run | 
| -> m a | 
Runs a Snap monad action only when the rqPathInfo of the request
 starts with the given path. For example,
dir "foo" handler
Will fail if rqPathInfo is not "/foo" or "/foo/...", and will
 add "foo/" to the handler's local rqContextPath.
ifTop :: MonadSnap m => m a -> m aSource
Runs a Snap monad action only when rqPathInfo is empty.
route :: MonadSnap m => [(ByteString, m a)] -> m aSource
A web handler which, given a mapping from URL entry points to web handlers, efficiently routes requests to the correct handler.
The URL entry points are given as relative paths, for example:
 route [ ("foo/bar/quux", fooBarQuux) ]
If the URI of the incoming request is
/foo/bar/quux
or
/foo/bar/quux/...anything...
then the request will be routed to "fooBarQuux", with rqContextPath
 set to "/foo/bar/quux/" and rqPathInfo set to
 "...anything...".
A path component within an URL entry point beginning with a colon (":")
 is treated as a variable capture; the corresponding path component within
 the request URI will be entered into the rqParams parameters mapping with
 the given name. For instance, if the routes were:
 route [ ("foo/:bar/baz", fooBazHandler) ]
Then a request for "/foo/saskatchewan/baz" would be routed to
 fooBazHandler with a mapping for:
"bar" => "saskatchewan"
in its parameters table.
Longer paths are matched first, and specific routes are matched before captures. That is, if given routes:
 [ ("a", h1), ("a/b", h2), ("a/:x", h3) ]
a request for "/a/b" will go to h2, "/a/s" for any s will
 go to h3, and "/a" will go to h1.
The following example matches "/article" to an article index,
 "/login" to a login, and "/article/..." to an article renderer.
 route [ ("article",     renderIndex)
       , ("article/:id", renderArticle)
       , ("login",       method POST doLogin) ]
URL decoding
A short note about URL decoding: path matching and variable capture are done
 on decoded URLs, but the contents of rqContextPath and rqPathInfo will
 contain the original encoded URL, i.e. what the user entered. For example,
 in the following scenario:
 route [ ("a b c d/", foo ) ]
A request for "/a+b+c+d" will be sent to foo with rqContextPath set
 to "a+b+c+d".
This behaviour changed as of Snap 0.6.1; previous versions had unspecified (and buggy!) semantics here.
routeLocal :: MonadSnap m => [(ByteString, m a)] -> m aSource
The routeLocal function is the same as route', except it doesn't
 change the request's context path. This is useful if you want to route to a
 particular handler but you want that handler to receive the rqPathInfo as
 it is.
Access to state
getsRequest :: MonadSnap m => (Request -> a) -> m aSource
getsResponse :: MonadSnap m => (Response -> a) -> m aSource
localRequest :: MonadSnap m => (Request -> Request) -> m a -> m aSource
withRequest :: MonadSnap m => (Request -> m a) -> m aSource
Fetches the Request from state and hands it to the given action.
withResponse :: MonadSnap m => (Response -> m a) -> m aSource
Fetches the Response from state and hands it to the given action.
Logging
Grabbing/transforming request bodies
runRequestBody :: MonadSnap m => Iteratee ByteString IO a -> m aSource
Sends the request body through an iteratee (data consumer) and returns the result.
If the iteratee you pass in here throws an exception, Snap will attempt to
 clear the rest of the unread request body before rethrowing the exception.
 If your iteratee used terminateConnection, however, Snap will give up and
 immediately close the socket.
getRequestBody :: MonadSnap m => m ByteStringSource
Returns the request body as a lazy bytestring.
This function is deprecated as of 0.6; it places no limits on the size of
 the request being read, and as such, if used, can result in a
 denial-of-service attack on your server. Please use readRequestBody
 instead.
Arguments
| :: MonadSnap m | |
| => Int64 | size of the largest request body we're willing
 to accept. If a request body longer than this is
 received, a  | 
| -> m ByteString | 
Returns the request body as a lazy bytestring. New in 0.6.
Arguments
| :: (forall a. Enumerator Builder IO a) | the output  | 
| -> Snap () | 
Normally Snap is careful to ensure that the request body is fully
 consumed after your web handler runs, but before the Response enumerator
 is streamed out the socket. If you want to transform the request body into
 some output in O(1) space, you should use this function.
Note that upon calling this function, response processing finishes early as
 if you called finishWith. Make sure you set any content types, headers,
 cookies, etc. before you call this function.
HTTP Datatypes and Functions
Contains all of the information about an incoming HTTP request.
Instances
| Show Request | |
| HasHeaders Request | |
| Monad m => MonadState Request (RequestBuilder m) | 
class HasHeaders a whereSource
A typeclass for datatypes which contain HTTP headers.
Methods
updateHeaders :: (Headers -> Headers) -> a -> aSource
Modify the datatype's headers.
Retrieve the headers from a datatype that has headers.
Instances
type Params = Map ByteString [ByteString]Source
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"].
Enumerates the HTTP method values (see http://tools.ietf.org/html/rfc2068.html#section-5.1.1).
A datatype representing an HTTP cookie.
Constructors
| Cookie | |
| Fields 
 | |
type HttpVersion = (Int, Int)Source
Headers
addHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> aSource
Adds a header key-value-pair to the HasHeaders datatype. If a header
 with the same name already exists, the new value is appended to the headers
 list.
setHeader :: HasHeaders a => CI ByteString -> ByteString -> a -> aSource
Sets a header key-value-pair in a HasHeaders datatype. If a header with
 the same name already exists, it is overwritten with the new value.
getHeader :: HasHeaders a => CI ByteString -> a -> Maybe ByteStringSource
Gets a header value out of a HasHeaders datatype. If many headers came
 in with the same name, they will be catenated together.
getHeaders :: HasHeaders a => CI ByteString -> a -> Maybe [ByteString]Source
Gets all of the values for a given header.
listHeaders :: HasHeaders a => a -> [(CI ByteString, ByteString)]Source
Lists all the headers out of a HasHeaders datatype. If many
 headers came in with the same name, they will be catenated together.
deleteHeader :: HasHeaders a => CI ByteString -> a -> aSource
Clears a header value from a HasHeaders datatype.
ipHeaderFilter :: MonadSnap m => m ()Source
Modifies the Request in the state to set the rqRemoteAddr
 field to the value in the X-Forwarded-For header. If the header is
 not present, this action has no effect.
This action should be used only when working behind a reverse http proxy that sets the X-Forwarded-For header. This is the only way to ensure the value in the X-Forwarded-For header can be trusted.
This is provided as a filter so actions that require the remote address can get it in a uniform manner. It has specifically limited functionality to ensure that its transformation can be trusted, when used correctly.
ipHeaderFilter' :: MonadSnap m => CI ByteString -> m ()Source
Modifies the Request in the state to set the rqRemoteAddr
 field to the value from the header specified.  If the header
 specified is not present, this action has no effect.
This action should be used only when working behind a reverse http proxy that sets the header being looked at. This is the only way to ensure the value in the header can be trusted.
This is provided as a filter so actions that require the remote address can get it in a uniform manner. It has specifically limited functionality to ensure that its transformation can be trusted, when used correctly.
Requests
rqServerName :: Request -> ByteStringSource
The server name of the request, as it came in from the request's
 Host: header.
rqServerPort :: Request -> IntSource
Returns the port number the HTTP server is listening on.
rqRemoteAddr :: Request -> ByteStringSource
The remote IP address.
rqRemotePort :: Request -> IntSource
The remote TCP port number.
rqLocalAddr :: Request -> ByteStringSource
The local IP address for this request.
rqLocalHostname :: Request -> ByteStringSource
Returns the HTTP server's idea of its local hostname.
rqIsSecure :: Request -> BoolSource
Returns True if this is an HTTPS session.
rqContentLength :: Request -> Maybe IntSource
Returns the Content-Length of the HTTP request body.
rqVersion :: Request -> HttpVersionSource
Returns the HTTP version used by the client.
rqCookies :: Request -> [Cookie]Source
Returns a list of the cookies that came in from the HTTP request headers.
rqPathInfo :: Request -> ByteStringSource
Handlers can be hung on a URI "entry point"; this is called the
 "context path". If a handler is hung on the context path
 "/foo/", and you request "/foo/bar", the value of
 rqPathInfo will be "bar".
The following identity holds:
 rqURI r == S.concat [ rqContextPath r
                     , rqPathInfo r
                     , let q = rqQueryString r
                       in if S.null q
                            then ""
                            else S.append "?" q
                     ]
rqContextPath :: Request -> ByteStringSource
The "context path" of the request; catenating rqContextPath,
 and rqPathInfo should get you back to the original rqURI
 (ignoring query strings). The rqContextPath always begins and ends
 with a slash ("/") character, and represents the path (relative
 to your component/snaplet) you took to get to your handler.
rqURI :: Request -> ByteStringSource
Returns the URI requested by the client.
rqQueryString :: Request -> ByteStringSource
Returns the HTTP query string for this Request.
rqParams :: Request -> ParamsSource
Returns the parameters mapping for this Request. "Parameters"
 are automatically decoded from the URI's query string and POST body
 and entered into this mapping. The rqParams value is thus a union of
 rqQueryParams and rqPostParams.
rqQueryParams :: Request -> ParamsSource
The parameter mapping decoded from the URI's query string.
rqPostParams :: Request -> ParamsSource
The parameter mapping decoded from the POST body. Note that Snap
 only auto-decodes POST request bodies when the request's
 Content-Type is application/x-www-form-urlencoded.
Arguments
| :: ByteString | parameter name to look up | 
| -> Request | HTTP request | 
| -> Maybe [ByteString] | 
Looks up the value(s) for the given named parameter. Parameters initially
 come from the request's query string and any decoded POST body (if the
 request's Content-Type is application/x-www-form-urlencoded).
 Parameter values can be modified within handlers using rqModifyParams.
Arguments
| :: ByteString | parameter name to look up | 
| -> Request | HTTP request | 
| -> Maybe [ByteString] | 
Looks up the value(s) for the given named parameter in the POST parameters mapping.
Arguments
| :: ByteString | parameter name to look up | 
| -> Request | HTTP request | 
| -> Maybe [ByteString] | 
Looks up the value(s) for the given named parameter in the query parameters mapping.
Arguments
| :: MonadSnap m | |
| => ByteString | parameter name to look up | 
| -> m (Maybe ByteString) | 
See rqParam. Looks up a value for the given named parameter in the
 Request. If more than one value was entered for the given parameter name,
 getParam gloms the values together with:
    intercalate " "Arguments
| :: MonadSnap m | |
| => ByteString | parameter name to look up | 
| -> m (Maybe ByteString) | 
See rqPostParam. Looks up a value for the given named parameter in the
 POST form parameters mapping in Request. If more than one value was
 entered for the given parameter name, getPostParam gloms the values
 together with:
    intercalate " "Arguments
| :: MonadSnap m | |
| => ByteString | parameter name to look up | 
| -> m (Maybe ByteString) | 
See rqQueryParam. Looks up a value for the given named parameter in the
 query string parameters mapping in Request. If more than one value was
 entered for the given parameter name, getQueryParam gloms the values
 together with:
    intercalate " "getPostParams :: MonadSnap m => m ParamsSource
getQueryParams :: MonadSnap m => m ParamsSource
rqModifyParams :: (Params -> Params) -> Request -> RequestSource
Modifies the parameters mapping (which is a Map ByteString ByteString)
 in a Request using the given function.
Arguments
| :: ByteString | parameter name | 
| -> [ByteString] | parameter values | 
| -> Request | request | 
| -> Request | 
Writes a key-value pair to the parameters mapping within the given request.
Responses
emptyResponse :: ResponseSource
An empty Response.
Sets the HTTP response code.
Arguments
| :: Int | HTTP response integer code | 
| -> ByteString | HTTP response explanation | 
| -> Response | Response to be modified | 
| -> Response | 
Sets the HTTP response status. Note: normally you would use
 setResponseCode unless you needed a custom response explanation.
rspStatusReason :: Response -> ByteStringSource
Returns the HTTP status explanation string.
setContentType :: ByteString -> Response -> ResponseSource
Sets the Content-Type in the Response headers.
Arguments
| :: ByteString | cookie name | 
| -> Response | response to query | 
| -> Maybe Cookie | 
Arguments
| :: ByteString | cookie name | 
| -> Response | response to modify | 
| -> Response | 
Arguments
| :: ByteString | cookie name | 
| -> (Cookie -> Cookie) | modifier function | 
| -> Response | response to modify | 
| -> Response | 
Arguments
| :: MonadSnap m | |
| => ByteString | Cookie name | 
| -> Maybe ByteString | Cookie domain | 
| -> m () | 
Expire the given Cookie in client's browser.
getCookie :: MonadSnap m => ByteString -> m (Maybe Cookie)Source
Gets the HTTP Cookie with the specified name.
readCookie :: (MonadSnap m, Readable a) => ByteString -> m aSource
Gets the HTTP Cookie with the specified name and decodes it.  If the
 decoding fails, the handler calls pass.
setContentLength :: Int64 -> Response -> ResponseSource
A note here: if you want to set the Content-Length for the response,
 Snap forces you to do it with this function rather than by setting it in
 the headers; the Content-Length in the headers will be ignored.
The reason for this is that Snap needs to look up the value of
 Content-Length for each request, and looking the string value up in the
 headers and parsing the number out of the text will be too expensive.
If you don't set a content length in your response, HTTP keep-alive will be
 disabled for HTTP/1.0 clients, forcing a Connection: close. For
 HTTP/1.1 clients, Snap will switch to the chunked transfer encoding if
 Content-Length is not specified.
clearContentLength :: Response -> ResponseSource
Removes any Content-Length set in the Response.
redirect :: MonadSnap m => ByteString -> m aSource
redirect' :: MonadSnap m => ByteString -> Int -> m aSource
Arguments
| :: Bool | if True, buffer the output, if False, send output immediately | 
| -> Response | |
| -> Response | 
The buffering mode controls whether Snap will buffer the output or not. You may wish to disable buffering when using Comet-like techniques which rely on the immediate sending of output data in order to maintain interactive semantics.
getBufferingMode :: Response -> BoolSource
The buffering mode controls whether Snap will buffer the output or not. You may wish to disable buffering when using Comet-like techniques which rely on the immediate sending of output data in order to maintain interactive semantics.
Response I/O
Arguments
| :: (forall a. Enumerator Builder IO a) | new response body enumerator | 
| -> Response | response to modify | 
| -> Response | 
Sets an HTTP response body to the given Enumerator value.
modifyResponseBody :: (forall a. Enumerator Builder IO a -> Enumerator Builder IO a) -> Response -> ResponseSource
Modifies a response body.
Arguments
| :: MonadSnap m | |
| => (forall a. Enumerator Builder IO a) | output to add | 
| -> m () | 
writeBuilder :: MonadSnap m => Builder -> m ()Source
writeBS :: MonadSnap m => ByteString -> m ()Source
Adds the given strict ByteString to the body of the Response stored
 in the Snap monad state.
Warning: This function is intentionally non-strict. If any pure
 exceptions are raised by the expression creating the ByteString,
 the exception won't actually be raised within the Snap handler.
writeLazyText :: MonadSnap m => Text -> m ()Source
Adds the given lazy Text to the body of the Response stored in the
 Snap monad state.
Warning: This function is intentionally non-strict. If any pure
 exceptions are raised by the expression creating the ByteString,
 the exception won't actually be raised within the Snap handler.
writeText :: MonadSnap m => Text -> m ()Source
Adds the given strict Text to the body of the Response stored in
 the Snap monad state.
Warning: This function is intentionally non-strict. If any pure
 exceptions are raised by the expression creating the ByteString,
 the exception won't actually be raised within the Snap handler.
writeLBS :: MonadSnap m => ByteString -> m ()Source
Adds the given lazy ByteString to the body of the Response stored
 in the Snap monad state.
Warning: This function is intentionally non-strict. If any pure
 exceptions are raised by the expression creating the ByteString,
 the exception won't actually be raised within the Snap handler.
sendFile :: MonadSnap m => FilePath -> m ()Source
Sets the output to be the contents of the specified file.
Calling sendFile will overwrite any output queued to be sent in the
 Response. If the response body is not modified after the call to
 sendFile, Snap will use the efficient sendfile() system call on
 platforms that support it.
If the response body is modified (using modifyResponseBody), the file
 will be read using mmap().
sendFilePartial :: MonadSnap m => FilePath -> (Int64, Int64) -> m ()Source
Sets the output to be the contents of the specified file, within the given (start,end) range.
Calling sendFilePartial will overwrite any output queued to be sent in
 the Response. If the response body is not modified after the call to
 sendFilePartial, Snap will use the efficient sendfile() system call on
 platforms that support it.
If the response body is modified (using modifyResponseBody), the file
 will be read using mmap().
Timeouts
setTimeout :: MonadSnap m => Int -> m ()Source
Causes the handler thread to be killed n seconds from now.
extendTimeout :: MonadSnap m => Int -> m ()Source
Causes the handler thread to be killed at least n seconds from now.
modifyTimeout :: MonadSnap m => (Int -> Int) -> m ()Source
Modifies the amount of time remaining before the request times out.
getTimeoutAction :: MonadSnap m => m (Int -> IO ())Source
Returns an IO action which you can use to set the handling thread's
 timeout value.
getTimeoutModifier :: MonadSnap m => m ((Int -> Int) -> IO ())Source
Returns an IO action which you can use to modify the timeout value.
Iteratee
type Enumerator a m b = Step a m b -> Iteratee a m b
Enumerators are sources of data, to be consumed by iteratees. Enumerators typically read from an external source (parser, handle, random generator, etc), then feed chunks into an tteratee until:
- The input source runs out of data.
- The iteratee yields a result value.
- The iteratee throws an exception.
newtype SomeEnumerator Source
An existential wrapper for the 'Enumerator ByteString IO a' type
Constructors
| SomeEnumerator (forall a. Enumerator ByteString IO a) | 
HTTP utilities
formatHttpTime :: CTime -> IO ByteStringSource
Converts a CTime into an HTTP timestamp.
parseHttpTime :: ByteString -> IO CTimeSource
Converts an HTTP timestamp into a CTime.
parseUrlEncoded :: ByteString -> Map ByteString [ByteString]Source
Parses a string encoded in application/x-www-form-urlencoded format.
urlEncode :: ByteString -> ByteStringSource
URL-escapes a string (see http://tools.ietf.org/html/rfc2396.html#section-2.4)
urlEncodeBuilder :: ByteString -> BuilderSource
URL-escapes a string (see
 http://tools.ietf.org/html/rfc2396.html#section-2.4) into a Builder.
urlDecode :: ByteString -> Maybe ByteStringSource
Decodes an URL-escaped string (see http://tools.ietf.org/html/rfc2396.html#section-2.4)