Safe Haskell | Trustworthy |
---|
- data HttpReq s = HttpReq {
- reqScheme :: !ByteString
- reqMethod :: !ByteString
- reqPath :: !ByteString
- reqPathLst :: ![ByteString]
- reqPathParams :: ![ByteString]
- reqPathCtx :: ![ByteString]
- reqQuery :: !ByteString
- reqHost :: !ByteString
- reqPort :: !(Maybe Int)
- reqVers :: !(Int, Int)
- reqHeaders :: ![(ByteString, ByteString)]
- reqCookies :: ![(ByteString, ByteString)]
- reqContentType :: !(Maybe (ByteString, [(ByteString, ByteString)]))
- reqContentLength :: !(Maybe Int)
- reqTransferEncoding :: !ByteString
- reqIfModifiedSince :: !(Maybe UTCTime)
- reqSession :: s
- defaultHttpReq :: HttpReq ()
- reqNormalPath :: HttpReq s -> ByteString
- httpReqI :: Monad m => Iter ByteString m (HttpReq ())
- inumHttpBody :: Monad m => HttpReq s -> Inum ByteString ByteString m a
- inumToChunks :: Monad m => Inum ByteString ByteString m a
- inumFromChunks :: Monad m => Inum ByteString ByteString m a
- http_fmt_time :: UTCTime -> String
- dateI :: Monad m => Iter ByteString m UTCTime
- data FormField = FormField {
- ffName :: !ByteString
- ffParams :: ![(ByteString, ByteString)]
- ffHeaders :: ![(ByteString, ByteString)]
- foldForm :: Monad m => HttpReq s -> (a -> FormField -> Iter ByteString m a) -> a -> Iter ByteString m a
- enumHttpReq :: Monad m => HttpReq s -> L -> Onum L m a
- data HttpStatus = HttpStatus !Int !ByteString
- stat100, stat501, stat500, stat405, stat404, stat403, stat401, stat400, stat307, stat304, stat303, stat302, stat301, stat200 :: HttpStatus
- data HttpResp m = HttpResp {
- respStatus :: !HttpStatus
- respHeaders :: ![(ByteString, ByteString)]
- respChunk :: !Bool
- respBody :: !(Onum ByteString m (IterR ByteString m ()))
- defaultHttpResp :: Monad m => HttpResp m
- respAddHeader :: (ByteString, ByteString) -> HttpResp m -> HttpResp m
- mkHttpHead :: Monad m => HttpStatus -> HttpResp m
- mkHtmlResp :: Monad m => HttpStatus -> ByteString -> HttpResp m
- mkContentLenResp :: Monad m => HttpStatus -> String -> ByteString -> HttpResp m
- mkOnumResp :: Monad m => HttpStatus -> String -> Onum ByteString m (IterR ByteString m ()) -> HttpResp m
- resp301 :: Monad m => String -> HttpResp m
- resp303 :: Monad m => String -> HttpResp m
- resp403 :: Monad m => HttpReq s -> HttpResp m
- resp404 :: Monad m => HttpReq s -> HttpResp m
- resp405 :: Monad m => HttpReq s -> HttpResp m
- resp500 :: Monad m => String -> HttpResp m
- enumHttpResp :: Monad m => HttpResp m -> Onum ByteString m ()
- httpRespI :: MonadIO m => Iter L m (HttpResp m)
- type HttpRequestHandler m s = HttpReq s -> Iter ByteString m (HttpResp m)
- data HttpServerConf m = HttpServerConf {
- srvLogger :: !(String -> Iter ByteString m ())
- srvDate :: !(Iter ByteString m (Maybe UTCTime))
- srvHandler :: !(HttpRequestHandler m ())
- nullHttpServer :: Monad m => HttpRequestHandler m () -> HttpServerConf m
- ioHttpServer :: MonadIO m => HttpRequestHandler m () -> HttpServerConf m
- inumHttpServer :: Monad m => HttpServerConf m -> Inum ByteString ByteString m ()
- absUri :: Monad m => Iter L m (S, S, Maybe Int, S, S)
- uri :: Monad m => Iter L m (S, S, Maybe Int, S, S)
- path2list :: S -> [S]
HTTP Request support
Data structure representing an HTTP request message.
HttpReq | |
|
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 structure representing the name and metadata of a control in a submitted form.
FormField | |
|
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
stat100, stat501, stat500, stat405, stat404, stat403, stat401, stat400, stat307, stat304, stat303, stat302, stat301, stat200 :: HttpStatusSource
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.
HttpResp | |
|
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.
:: Monad m | |
=> HttpStatus | |
-> ByteString | Body as a pure lazy |
-> HttpResp m |
Generate an HttpResp
with a body of type text/html
.
:: 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.
:: Monad m | |
=> HttpStatus | |
-> String | Value for Content-Type header: |
-> Onum ByteString m (IterR ByteString m ()) |
|
-> HttpResp m |
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
.
HttpServerConf | |
|
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.
:: 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).
Turn a path into a list of components. Used to set the
reqPathLst
field in a request.