snap-core-0.1.1: Snap: A Haskell Web Framework (Core)

Snap.Types

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.

Synopsis

The Snap Monad

data Snap a Source

Snap is the Monad that user web handlers run in. Snap gives you:

  1. stateful access to fetch or modify an HTTP Request
  2. stateful access to fetch or modify an HTTP Response
  3. failure / Alternative / MonadPlus semantics: a Snap handler can choose not to handle a given request, using empty or its synonym pass, 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
  1. convenience functions (writeBS, writeLBS, writeText, writeLazyText, addToOutput) for writing output to the Response:
 a :: (forall a . Enumerator a) -> Snap ()
 a someEnumerator = do
     writeBS "I'm a strict bytestring"
     writeLBS "I'm a lazy bytestring"
     addToOutput someEnumerator
  1. 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.

  1. access to the IO monad through a MonadIO instance:
 a :: Snap ()
 a = liftIO fireTheMissiles

runSnap :: Snap a -> Request -> Iteratee IO (Request, Response)Source

Runs a Snap monad action in the 'Iteratee IO' monad.

data NoHandlerException Source

This exception is thrown if the handler you supply to runSnap fails.

Constructors

NoHandlerException 

Functions for control flow and early termination

finishWith :: Response -> Snap ()Source

Short-circuits a Snap monad action early, storing the given Response value in its state.

pass :: Snap 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.

Routing

method :: Method -> Snap a -> Snap aSource

Runs a Snap monad action only if the request's HTTP method matches the given method.

pathSource

Arguments

:: ByteString

path to match against

-> Snap a

handler to run

-> Snap 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.

dirSource

Arguments

:: ByteString

path component to match

-> Snap a

handler to run

-> Snap 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 :: Snap a -> Snap aSource

Runs a Snap monad action only when rqPathInfo is empty.

route :: [(ByteString, Snap a)] -> Snap 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...".

FIXME/TODO: we need a version with and without the context path setting behaviour; if the route is "article/:id/print", we probably want the contextPath to be "/article" instead of "/article/whatever/print".

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) ]

routeLocal :: [(ByteString, Snap a)] -> Snap 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

getRequest :: Snap RequestSource

Grabs the Request object out of the Snap monad.

getResponse :: Snap ResponseSource

Grabs the Response object out of the Snap monad.

putRequest :: Request -> Snap ()Source

Puts a new Request object into the Snap monad.

putResponse :: Response -> Snap ()Source

Puts a new Response object into the Snap monad.

modifyRequest :: (Request -> Request) -> Snap ()Source

Modifies the Request object stored in a Snap monad.

modifyResponse :: (Response -> Response) -> Snap ()Source

Modifes the Response object stored in a Snap monad.

localRequest :: (Request -> Request) -> Snap a -> Snap aSource

Runs a Snap action with a locally-modified Request state object. The Request object in the Snap monad state after the call to localRequest will be unchanged.

withRequest :: (Request -> Snap a) -> Snap aSource

Fetches the Request from state and hands it to the given action.

withResponse :: (Response -> Snap a) -> Snap aSource

Fetches the Response from state and hands it to the given action.

Grabbing request bodies

runRequestBody :: Iteratee IO a -> Snap aSource

Sends the request body through an iteratee (data consumer) and returns the result.

getRequestBody :: Snap ByteStringSource

Returns the request body as a bytestring.

unsafeDetachRequestBody :: Snap (Enumerator a)Source

Detaches the request body's Enumerator from the Request and returns it. You would want to use this if you needed to send the HTTP request body (transformed or otherwise) through to the output in O(1) space. (Examples: transcoding, "echo", etc)

Normally Snap is careful to ensure that the request body is fully consumed after your web handler runs; this function is marked "unsafe" because it breaks this guarantee and leaves the responsibility up to you. If you don't fully consume the Enumerator you get here, the next HTTP request in the pipeline (if any) will misparse. Be careful with exception handlers.

HTTP Datatypes and Functions

HTTP-related datatypes: Request, Response, Cookie, etc.

data Request Source

Contains all of the information about an incoming HTTP request.

data Response Source

Represents an HTTP response.

type Headers = Map CIByteString [ByteString]Source

A type alias for a case-insensitive key-value mapping.

class HasHeaders a whereSource

A typeclass for datatypes which contain HTTP headers.

Methods

updateHeaders :: (Headers -> Headers) -> a -> aSource

Modify the datatype's headers.

headers :: a -> HeadersSource

Retrieve the headers from a datatype that has headers.

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&param=bar2"), looking up "param" in the mapping will give you ["bar1", "bar2"].

data Method Source

Enumerates the HTTP method values (see http://tools.ietf.org/html/rfc2068.html#section-5.1.1).

Constructors

GET 
HEAD 
POST 
PUT 
DELETE 
TRACE 
OPTIONS 
CONNECT 

data Cookie Source

A datatype representing an HTTP cookie.

Constructors

Cookie 

Fields

cookieName :: !ByteString

The name of the cookie.

cookieValue :: !ByteString

The cookie's string value.

cookieExpires :: !(Maybe UTCTime)

The cookie's expiration value, if it has one.

cookieDomain :: !(Maybe ByteString)

The cookie's "domain" value, if it has one.

cookiePath :: !(Maybe ByteString)

The cookie path.

Instances

Headers

addHeader :: HasHeaders a => CIByteString -> 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 => CIByteString -> 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 => CIByteString -> 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.

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 (currently always False).

rqContentLength :: Request -> Maybe IntSource

Returns the Content-Length of the HTTP request body.

rqMethod :: Request -> MethodSource

Returns the HTTP request method.

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 (will be; --ed) 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".

rqContextPath :: Request -> ByteStringSource

The "context path" of the request; catenating rqContextPath, and rqPathInfo should get you back to the original rqURI. 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 Params mapping for this Request. "Parameters" are automatically decoded from the query string and POST body and entered into this mapping.

rqParamSource

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.

getParamSource

Arguments

:: ByteString

parameter name to look up

-> Snap (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 " "

rqModifyParams :: (Params -> Params) -> Request -> RequestSource

Modifies the parameters mapping (which is a Map ByteString ByteString) in a Request using the given function.

rqSetParamSource

Arguments

:: ByteString

parameter name

-> [ByteString]

parameter values

-> Request

request

-> Request 

Writes a key-value pair to the parameters mapping within the given request.

Responses

setResponseStatusSource

Arguments

:: Int

HTTP response integer code

-> ByteString

HTTP response explanation

-> Response

Response to be modified

-> Response 

Sets the HTTP response status.

rspStatus :: Response -> IntSource

Returns the HTTP status code.

rspStatusReason :: Response -> ByteStringSource

Returns the HTTP status explanation string.

setContentType :: ByteString -> Response -> ResponseSource

Sets the Content-Type in the Response headers.

addCookieSource

Arguments

:: Cookie

cookie value

-> Response

response to modify

-> Response 

Adds an HTTP Cookie to the Response headers.

setContentLength :: Int -> 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.

Response I/O

setResponseBodySource

Arguments

:: (forall a. Enumerator a)

new response body enumerator

-> Response

response to modify

-> Response 

Sets an HTTP response body to the given Enumerator value.

modifyResponseBody :: (forall a. Enumerator a -> Enumerator a) -> Response -> ResponseSource

Modifies a response body.

addToOutputSource

Arguments

:: (forall a. Enumerator a)

output to add

-> Snap () 

Adds the output from the given enumerator to the Response stored in the Snap monad state.

writeBS :: ByteString -> Snap ()Source

Adds the given strict ByteString to the body of the Response stored in the Snap monad state.

writeLazyText :: Text -> Snap ()Source

Adds the given lazy Text to the body of the Response stored in the Snap monad state.

writeText :: Text -> Snap ()Source

Adds the given strict Text to the body of the Response stored in the Snap monad state.

writeLBS :: ByteString -> Snap ()Source

Adds the given lazy ByteString to the body of the Response stored in the Snap monad state.

sendFile :: FilePath -> Snap ()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().

Iteratee

HTTP utilities

formatHttpTime :: CTime -> IO ByteStringSource

Converts a CTime into an HTTP timestamp.

parseHttpTime :: ByteString -> IO CTimeSource

Converts an HTTP timestamp into a CTime.