HTTP-4000.0.0

Portabilitynon-portable (not tested)
Stabilityexperimental
MaintainerSigbjorn Finne <sigbjorn.finne@gmail.com>

Network.HTTP.Base

Contents

Description

An easy HTTP interface; base types.

Synopsis

Constants

HTTP

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.

Constructors

HEAD 
PUT 
GET 
POST 
DELETE 
OPTIONS 
TRACE 

data HTTPRequest a Source

An HTTP Request. The Show instance of this type is used for message serialisation, which means no body data is output.

Constructors

Request 

Fields

rqURI :: URI

might need changing in future 1) to support * uri in OPTIONS request 2) transparent support for both relative & absolute uris, although this should already work (leave scheme & host parts empty).

rqMethod :: RequestMethod
 
rqHeaders :: [Header]
 
rqBody :: a
 

data HTTPResponse a Source

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.

Constructors

Response 

URL Encoding

URI authority parsing

parseURIAuthority :: String -> Maybe URIAuthoritySource

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.

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.

getAuth :: Monad m => HTTPRequest ty -> m URIAuthoritySource

getAuth req fishes out the authority portion of the URL in a request's Host header.

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

catchIO :: IO a -> (IOException -> IO a) -> IO aSource

catchIO a h handles IO action exceptions throughout codebase; version-specific tweaks better go here.

catchIO_ :: IO a -> IO a -> IO aSource