Copyright | See LICENSE file |
---|---|
License | BSD |
Maintainer | Ganesh Sittampalam <ganesh@earth.li> |
Stability | experimental |
Portability | non-portable (not tested) |
Safe Haskell | Safe |
Language | Haskell98 |
Definitions of Request
and Response
types along with functions
for normalizing them. It is assumed to be an internal module; user
code should, if possible, import Network.HTTP
to access the functionality
that this module provides.
Additionally, the module exports internal functions for working with URLs, and for handling the processing of requests and responses coming back.
- httpVersion :: String
- data Request a = Request {}
- data Response a = Response {
- rspCode :: ResponseCode
- rspReason :: String
- rspHeaders :: [Header]
- rspBody :: a
- data RequestMethod
- type Request_String = Request String
- type Response_String = Response String
- type HTTPRequest a = Request a
- type HTTPResponse a = Response a
- urlEncode :: String -> String
- urlDecode :: String -> String
- urlEncodeVars :: [(String, String)] -> String
- data URIAuthority = URIAuthority {}
- parseURIAuthority :: String -> Maybe URIAuthority
- uriToAuthorityString :: URI -> String
- uriAuthToString :: URIAuth -> String
- uriAuthPort :: Maybe URI -> URIAuth -> Int
- reqURIAuth :: Request ty -> URIAuth
- parseResponseHead :: [String] -> Result ResponseData
- parseRequestHead :: [String] -> Result RequestData
- data ResponseNextStep
- matchResponse :: RequestMethod -> ResponseCode -> ResponseNextStep
- type ResponseData = (ResponseCode, String, [Header])
- type ResponseCode = (Int, Int, Int)
- type RequestData = (RequestMethod, URI, [Header])
- data NormalizeRequestOptions ty = NormalizeRequestOptions {
- normDoClose :: Bool
- normForProxy :: Bool
- normUserAgent :: Maybe String
- normCustoms :: [RequestNormalizer ty]
- defaultNormalizeRequestOptions :: NormalizeRequestOptions ty
- type RequestNormalizer ty = NormalizeRequestOptions ty -> Request ty -> Request ty
- normalizeRequest :: NormalizeRequestOptions ty -> Request ty -> Request ty
- splitRequestURI :: URI -> (String, URI)
- getAuth :: Monad m => Request ty -> m URIAuthority
- normalizeRequestURI :: Bool -> String -> Request ty -> Request ty
- normalizeHostHeader :: Request ty -> Request ty
- findConnClose :: [Header] -> Bool
- linearTransfer :: (Int -> IO (Result a)) -> Int -> IO (Result ([Header], a))
- hopefulTransfer :: BufferOp a -> IO (Result a) -> [a] -> IO (Result ([Header], a))
- chunkedTransfer :: BufferOp a -> IO (Result a) -> (Int -> IO (Result a)) -> IO (Result ([Header], a))
- uglyDeathTransfer :: String -> IO (Result ([Header], a))
- readTillEmpty1 :: BufferOp a -> IO (Result a) -> IO (Result [a])
- readTillEmpty2 :: BufferOp a -> IO (Result a) -> [a] -> IO (Result [a])
- defaultGETRequest :: URI -> Request_String
- defaultGETRequest_ :: BufferType a => URI -> Request a
- mkRequest :: BufferType ty => RequestMethod -> URI -> Request ty
- setRequestBody :: Request_String -> (String, String) -> Request_String
- defaultUserAgent :: String
- httpPackageVersion :: String
- libUA :: String
- catchIO :: IO a -> (IOException -> IO a) -> IO a
- catchIO_ :: IO a -> IO a -> IO a
- responseParseError :: String -> String -> Result a
- getRequestVersion :: Request a -> Maybe String
- getResponseVersion :: Response a -> Maybe String
- setRequestVersion :: String -> Request a -> Request a
- setResponseVersion :: String -> Response a -> Response a
- failHTTPS :: Monad m => URI -> m ()
Constants
HTTP
An HTTP Request.
The Show
instance of this type is used for message serialisation,
which means no body data is output.
An HTTP Response.
The Show
instance of this type is used for message serialisation,
which means no body data is output, additionally the output will
show an HTTP version of 1.1 instead of the actual version returned
by a server.
Response | |
|
data RequestMethod Source
The HTTP request method, to be used in the Request
object.
We are missing a few of the stranger methods, but these are
not really necessary until we add full TLS.
type Request_String = Request String Source
type Response_String = Response String Source
type HTTPRequest a = Request a Source
type HTTPResponse a = Response a Source
URL Encoding
urlEncodeVars :: [(String, String)] -> String Source
URI authority parsing
data URIAuthority Source
parseURIAuthority :: String -> Maybe URIAuthority Source
Parse the authority part of a URL.
RFC 1732, section 3.1: //<user>:<password>@<host>:<port>/<url-path> Some or all of the parts "<user>:<password>@", ":<password>", ":<port>", and "/<url-path>" may be excluded.
uriToAuthorityString :: URI -> String Source
uriAuthToString :: URIAuth -> String Source
reqURIAuth :: Request ty -> URIAuth Source
parseResponseHead :: [String] -> Result ResponseData Source
parseRequestHead :: [String] -> Result RequestData Source
type ResponseData = (ResponseCode, String, [Header]) Source
ResponseData
contains the head of a response payload;
HTTP response code, accompanying text description + header
fields.
type ResponseCode = (Int, Int, Int) Source
For easy pattern matching, HTTP response codes xyz
are
represented as (x,y,z)
.
type RequestData = (RequestMethod, URI, [Header]) Source
RequestData
contains the head of a HTTP request; method,
its URL along with the auxillary/supporting header data.
data NormalizeRequestOptions ty Source
NormalizeRequestOptions
brings together the various defaulting/normalization options
over Request
s. Use defaultNormalizeRequestOptions
for the standard selection of option
type RequestNormalizer ty = NormalizeRequestOptions ty -> Request ty -> Request ty Source
RequestNormalizer
is the shape of a (pure) function that rewrites
a request into some normalized form.
normalizeRequest :: NormalizeRequestOptions ty -> Request ty -> Request ty Source
normalizeRequest opts req
is the entry point to use to normalize your
request prior to transmission (or other use.) Normalization is controlled
via the NormalizeRequestOptions
record.
splitRequestURI :: URI -> (String, URI) Source
getAuth :: Monad m => Request ty -> m URIAuthority Source
getAuth req
fishes out the authority portion of the URL in a request's Host
header.
normalizeRequestURI :: Bool -> String -> Request ty -> Request ty Source
Deprecated: Please use Network.HTTP.Base.normalizeRequest instead
normalizeHostHeader :: Request ty -> Request ty Source
Deprecated: Please use Network.HTTP.Base.normalizeRequest instead
findConnClose :: [Header] -> Bool Source
linearTransfer :: (Int -> IO (Result a)) -> Int -> IO (Result ([Header], a)) Source
Used when we know exactly how many bytes to expect.
hopefulTransfer :: BufferOp a -> IO (Result a) -> [a] -> IO (Result ([Header], a)) Source
Used when nothing about data is known, Unfortunately waiting for a socket closure causes bad behaviour. Here we just take data once and give up the rest.
chunkedTransfer :: BufferOp a -> IO (Result a) -> (Int -> IO (Result a)) -> IO (Result ([Header], a)) Source
A necessary feature of HTTP/1.1 Also the only transfer variety likely to return any footers.
uglyDeathTransfer :: String -> IO (Result ([Header], a)) Source
Maybe in the future we will have a sensible thing to do here, at that time we might want to change the name.
readTillEmpty1 :: BufferOp a -> IO (Result a) -> IO (Result [a]) Source
Remove leading crlfs then call readTillEmpty2 (not required by RFC)
readTillEmpty2 :: BufferOp a -> IO (Result a) -> [a] -> IO (Result [a]) Source
Read lines until an empty line (CRLF), also accepts a connection close as end of input, which is not an HTTP/1.1 compliant thing to do - so probably indicates an error condition.
defaultGETRequest_ :: BufferType a => URI -> Request a Source
mkRequest :: BufferType ty => RequestMethod -> URI -> Request ty Source
'mkRequest method uri' constructs a well formed request for the given HTTP method and URI. It does not normalize the URI for the request _nor_ add the required Host: header. That is done either explicitly by the user or when requests are normalized prior to transmission.
setRequestBody :: Request_String -> (String, String) -> Request_String Source
defaultUserAgent :: String Source
A default user agent string. The string is "haskell-HTTP/$version"
where $version
is the version of this HTTP package.
httpPackageVersion :: String Source
The version of this HTTP package as a string, e.g. "4000.1.2"
. This
may be useful to include in a user agent string so that you can determine
from server logs what version of this package HTTP clients are using.
This can be useful for tracking down HTTP compatibility quirks.
Deprecated: Use defaultUserAgent instead (but note the user agent name change)
Deprecated. Use defaultUserAgent
catchIO :: IO a -> (IOException -> IO a) -> IO a Source
catchIO a h
handles IO action exceptions throughout codebase; version-specific
tweaks better go here.
responseParseError :: String -> String -> Result a Source
getRequestVersion :: Request a -> Maybe String Source
getRequestVersion req
returns the HTTP protocol version of
the request req
. If Nothing
, the default httpVersion
can be assumed.
getResponseVersion :: Response a -> Maybe String Source
getResponseVersion rsp
returns the HTTP protocol version of
the response rsp
. If Nothing
, the default httpVersion
can be
assumed.
setRequestVersion :: String -> Request a -> Request a Source
setRequestVersion v req
returns a new request, identical to
req
, but with its HTTP version set to v
.
setResponseVersion :: String -> Response a -> Response a Source
setResponseVersion v rsp
returns a new response, identical to
rsp
, but with its HTTP version set to v
.