iterIO-0.2.2: Iteratee-based IO with pipe operators

Safe HaskellTrustworthy

Data.IterIO.Http

Contents

Synopsis

HTTP Request support

data HttpReq s Source

Data structure representing an HTTP request message.

Constructors

HttpReq 

Fields

reqScheme :: !ByteString

Scheme (e.g., 'http', 'https', ...)

reqMethod :: !ByteString

Method (e.g., GET, POST, ...).

reqPath :: !ByteString

Raw path from the URL (not needed if you use reqPathList and reqPathParams).

reqPathLst :: ![ByteString]

URL request path, broken into a list of directory components, and normalized to remove "." and process "..".

reqPathParams :: ![ByteString]

Used by routeVar to save pathname components that are variables (used as a stack, so the last variable saved is the first one in the list).

reqPathCtx :: ![ByteString]

Stores pathname components that have been stripped off of reqPathLst during routing.

reqQuery :: !ByteString

The portion of the URL after the ? character (if any).

reqHost :: !ByteString

Lower-case host header (or the host from the request line, if the request is for an absolute URI).

reqPort :: !(Maybe Int)

Port number if supplied in Host header.

reqVers :: !(Int, Int)

HTTP version major and minor number from the request line.

reqHeaders :: ![(ByteString, ByteString)]

List of all header field names and values in the HTTP request. Field names are converted to lowercase to allow easier searching.

reqCookies :: ![(ByteString, ByteString)]

List of Cookies supplied in the request.

reqContentType :: !(Maybe (ByteString, [(ByteString, ByteString)]))

Parsed version of the Content-Type header, if any. The first ByteString is the actual content type. Following this is a list of parameter names and values. The most useful parameter is "boundary", used with the multipart/form-data content type.

reqContentLength :: !(Maybe Int)

Value of the content-Length header, if any.

reqTransferEncoding :: !ByteString

The Transfer-Encoding header.

reqIfModifiedSince :: !(Maybe UTCTime)

Time from the If-Modified-Since header (if present)

reqSession :: s

Application-specific session information

Instances

reqNormalPath :: HttpReq s -> ByteStringSource

Returns a normalized version of the full requested path (including all context in reqCtx) in the URL (e.g., where "." has been eliminated, ".." has been processed, there is exactly one '/' between each directory component, and the query has been stripped off).

httpReqI :: Monad m => Iter ByteString m (HttpReq ())Source

Parse an HTTP header, returning an HttpReq data structure.

inumHttpBody :: Monad m => HttpReq s -> Inum ByteString ByteString m aSource

This Inum reads to the end of an HTTP message body (and not beyond) and decodes the Transfer-Encoding. It handles straight content of a size specified by the Content-Length header and chunk-encoded content.

inumToChunks :: Monad m => Inum ByteString ByteString m aSource

An HTTP Chunk encoder (as specified by RFC 2616).

inumFromChunks :: Monad m => Inum ByteString ByteString m aSource

An HTTP Chunk decoder (as specified by RFC 2616).

http_fmt_time :: UTCTime -> StringSource

Formats a time in the format specified by RFC 2616.

dateI :: Monad m => Iter ByteString m UTCTimeSource

Parses a Date/Time string in any one of the three formats specified by RFC 2616.

data FormField Source

Data structure representing the name and metadata of a control in a submitted form.

Constructors

FormField 

Fields

ffName :: !ByteString

Name of the form control being processed

ffParams :: ![(ByteString, ByteString)]

Parameters from the Content-Disposition: header. This only applies to Content-Type: multipart/form-data, and will be empty for forms of type application/x-www-form-urlencoded or forms submitted in the URL parameters of a GET request.

ffHeaders :: ![(ByteString, ByteString)]

Extra headers following the Content-Disposition: header of a multipart/form-data post. Empty for other kinds of form submission.

Instances

foldForm :: Monad m => HttpReq s -> (a -> FormField -> Iter ByteString m a) -> a -> Iter ByteString m aSource

Parses a form, and folds a function over each control. The value of each control is available through Iteratee input. Thus, you can extract the submitted value with pureI, or redirect it elsewhere by executing another Iter. For example, to parse a form and print it to standard output (without buffering possibly large file uploads in memory):

  do let docontrol _ field = do
           liftIO $ putStrLn $
               "The value of " ++ (S8.unpack $ ffName field) ++ " is:"
           stdoutI                   -- Send form value to standard output
           liftIO $ putStrLn "\n"
     foldForm req docontrol ()

Or to produce a list of (field, value) pairs, you can say something like:

  do let docontrol acc field = do
           val <- pureI
           return $ (ffName field, val) : acc
     foldForm req docontrol []

Note that for POSTed forms of enctype application/x-www-form-urlencoded, foldForm will read to the end of its input. Thus, it is important to ensure foldForm is called from within an inumHttpBody enumerator (which is guaranteed by inumHttpServer).

enumHttpReq :: Monad m => HttpReq s -> L -> Onum L m aSource

Enumerate a request, and body.

HTTP Response support

data HttpStatus Source

HTTP status code and text description of response, for the first line of an HTTP response message. A bunch of pre-defined statuses from RFC 2616 are supplied under the names stat200, stat404, stat500, etc.

Constructors

HttpStatus !Int !ByteString 

data HttpResp m Source

A data structure describing an HTTP response message to be sent, parameterized by the Monad in which the response will be written to the network.

Constructors

HttpResp 

Fields

respStatus :: !HttpStatus

The response status.

respHeaders :: ![(ByteString, ByteString)]

Headers to send back

respChunk :: !Bool

True if the message body should be passed through inumToChunks and a "Transfer-Encoding: chunked" header should be added. Generally this should be True unless you have added a Content-Length header, manually set up chunk encoding by fusing it in respBody, or are not returning a message body with the reply.

respBody :: !(Onum ByteString m (IterR ByteString m ()))

Onum producing the message body. Use inumNull (which is an empty Inum) to produce an empty body for responses that do not contain a body.

Instances

defaultHttpResp :: Monad m => HttpResp mSource

An empty HTTP response, to which you must add headers and possibly a message body.

respAddHeader :: (ByteString, ByteString) -> HttpResp m -> HttpResp mSource

Add header to the HTTP response.

mkHttpHead :: Monad m => HttpStatus -> HttpResp mSource

Generate an HttpResp without a body.

mkHtmlRespSource

Arguments

:: Monad m 
=> HttpStatus 
-> ByteString

Body as a pure lazy ByteString

-> HttpResp m 

Generate an HttpResp with a body of type text/html.

mkContentLenRespSource

Arguments

:: Monad m 
=> HttpStatus 
-> String

Value for Content-Type: header

-> ByteString

Contents of response body

-> HttpResp m 

Make an HttpResp of an arbitrary content-type based on a pure lazy ByteString. Since the result is pure, this function first measures its length so as to set a Content-Length header instead of using HTTP chunk encoding.

mkOnumRespSource

Arguments

:: Monad m 
=> HttpStatus 
-> String

Value for Content-Type header:

-> Onum ByteString m (IterR ByteString m ())

Onum that will generate reply body dynamically.

-> HttpResp m 

Make an HttpResp of an arbitrary content-type based on an Onum that will dynamically generate the message body. Since the message body is generated dynamically, the reply will use an HTTP chunk encoding.

resp301 :: Monad m => String -> HttpResp mSource

Generate a 301 (redirect) response.

resp303 :: Monad m => String -> HttpResp mSource

Generate a 303 (see other) response.

resp403 :: Monad m => HttpReq s -> HttpResp mSource

Generate a 403 (forbidden) response.

resp404 :: Monad m => HttpReq s -> HttpResp mSource

Generate a 404 (not found) response.

resp405 :: Monad m => HttpReq s -> HttpResp mSource

Generate a 405 (method not allowed) response.

resp500 :: Monad m => String -> HttpResp mSource

Generate a 500 (internal server error) response.

enumHttpResp :: Monad m => HttpResp m -> Onum ByteString m ()Source

Format and enumerate a response header and body.

httpRespI :: MonadIO m => Iter L m (HttpResp m)Source

Return a response. If the 'Trasnfer-Encoding' header is set to 'chunked', it is removed from the headers and the respChunk field is set. enumHttpResp to enumerate the headers and body.

HTTP connection handling

type HttpRequestHandler m s = HttpReq s -> Iter ByteString m (HttpResp m)Source

Given the headers of an HTTP request, provides an iteratee that will process the request body (if any) and return a response.

data HttpServerConf m Source

Data structure describing the configuration of an HTTP server for inumHttpServer.

nullHttpServer :: Monad m => HttpRequestHandler m () -> HttpServerConf mSource

Generate a null HttpServerConf structure with no logging and no Date header.

ioHttpServer :: MonadIO m => HttpRequestHandler m () -> HttpServerConf mSource

Generate an HttpServerConf structure that uses IO calls to log to standard error and get the current time for the Date header.

inumHttpServerSource

Arguments

:: Monad m 
=> HttpServerConf m

Server configuration

-> Inum ByteString ByteString m () 

An Inum that behaves like an HTTP server. The file Examples/httptest.hs that comes with the iterIO distribution gives an example of how to use this function.

URI parsers

absUri :: Monad m => Iter L m (S, S, Maybe Int, S, S)Source

Parses an absoluteURI, returning (scheme, host, path, query)

uri :: Monad m => Iter L m (S, S, Maybe Int, S, S)Source

Parses a Request-URI, defined by RFC2616, and returns (scheme, host, path, query).

path2list :: S -> [S]Source

Turn a path into a list of components. Used to set the reqPathLst field in a request.