uhttpc-0.1.1.0: Minimal HTTP client library optimized for benchmarking

Safe HaskellNone
LanguageHaskell2010

Network.HTTP.MicroClient

Contents

Description

Minimal HTTP client implementation

Note: this implementation only supports a subset of the HTTP protocol for performance-reasons. This implementation is not meant to be used for more than benchmarking purposes.

See doReq in src-exe/uhttpc-bench.hs for an usage example of this API

Synopsis

Socket Stream abstract data type

data SockStream Source

Minimal socket input-stream abstraction w/ single pushback & consumed byte-count

This abstraction is inspired by io-streams but is tuned for low-overhead

ssFromSocket :: Socket -> IO SockStream Source

Convert an existing Socket into a SockStream

ssConnect :: Maybe SockAddr -> SockAddr -> IO SockStream Source

Wrapper that creates TCP/IP IPv4 SocketStream and connects to SockAddr created with getSockAddr

If provided, the Maybe SockAddr argument allows to locally bind the socket to a specific source address.

ssToSocket :: SockStream -> Socket Source

Access underlying Socket

ssId :: SockStream -> Int Source

Access SockStream counter id

Each created SockStream wrapper has an unique counter id value associated

ssRead :: SockStream -> IO ByteString Source

Read data from stream.

Note: Returns empty string on EOF. It's often better to use ssRead' instead.

ssPeek :: SockStream -> IO ByteString Source

Version of ssRead which does not consume the data returned

That is, ssPeek ss is semantically equivalent to do { b <- ssRead ss; ssUnRead b ss; return b}.

ssPeek is idempotent, i.e. ssPeek ss == ssPeek ss >> ssPeek ss

ssPeekBuf :: SockStream -> IO ByteString Source

May return empty string if no data has been buffered yet

ssRead' :: SockStream -> IO ByteString Source

Version of ssRead that throws

ssReadN :: SockStream -> Word64 -> IO ByteString Source

Read exactly n bytes from SocketStream; throws exception if connection is closed

ssUnRead :: ByteString -> SockStream -> IO () Source

Push-back read data into SockStream

ssWrite :: ByteString -> SockStream -> IO () Source

Write data out to socket (uses sendAll internally)

ssReadCnt :: SockStream -> IO Word64 Source

Returns length of data consumed (i.e. w/o ssUnRead data)

ssWriteCnt :: SockStream -> IO Word64 Source

Returns length of data written to stream

HTTP Protocol Handling

data HttpResponse Source

Constructors

HttpResponse 

Fields

respCode :: !HttpCode

status code

respKeepalive :: !Bool

whether server keeps connection open

respContentLen :: !Word64

content length

respHeader :: [MsgHeader]

list of header lines w/o CRLF

respContent :: [ByteString]

list of chunks

type HttpCode = Int Source

HTTP status code

data Method Source

RFC2616 sec 5.1.1 Method

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 

type ReqURI Source

Arguments

 = ByteString

RFC2616 sec 5.1.2 Request-URI (e.g. "pubindex.html")

type HostPort Source

Arguments

 = ByteString

RFC2616 sec 14.3 host [ ":" port ] (e.g. "localhost:8001")

type MsgHeader Source

Arguments

 = ByteString

RFC2616 sec 4.2 message-header (e.g. "Content-Type: text/plain"

data TransferEncoding Source

transfer-encoding/content-length information

Constructors

TeIdentity !Word64

identity w/ content length

TeChunked

chunked transfer

TeInvalid 

mkHttp11Req Source

Arguments

:: Method 
-> ReqURI 
-> HostPort 
-> Bool

if False sets Connection: close header

-> [MsgHeader]

additional HTTP request headers

-> Maybe ByteString

optional request body

-> ByteString

Request constructed as a ByteString ready to be sent over the wire

Construct general HTTP/1.1 request.

mkHttp11GetReq :: ReqURI -> HostPort -> Bool -> [MsgHeader] -> ByteString Source

Construct HTTP/1.1 GET request. See mkHttp11Req for constructing more general requests.

recvHttpResponse :: SockStream -> IO HttpResponse Source

Receive full HTTP response

internal helpers of recvHttpResponse

recvHttpHeaders :: SockStream -> IO [ByteString] Source

Receive/consume HTTP response from SockStream

If no exception occured during recvHttpHeaders the SockStream is left at the beginning of the (potentially empty) HTTP response body.

httpHeaderGetInfos :: [ByteString] -> (HttpCode, Bool, TransferEncoding) Source

Extract information from the header lines as returned by recvHttpHeaders

returns: (status-code, close-conn, Just content-length or Nothing (i.e. chunked))

recvChunk :: SockStream -> IO ByteString Source

Receive single HTTP chunk

Utilities

splitUrl :: String -> Either String (String, PortNumber, String) Source

Split HTTP URL into (hostname,port,url-path)

getPOSIXTimeSecs :: IO Double Source

Return the time as the number of seconds (with up to microsecond precision) since the Epoch, 1970-01-01 00:00:00 +0000 (UTC).

This is a faster implementation the code below useful for benchmarking purposes.

import Data.Time.Clock.POSIX (getPOSIXTime)

getPOSIXTimeSecs :: IO Double
getPOSIXTimeSecs = fmap realToFrac getPOSIXTime

Note: this function returns NaN in case the underlying gettimeofday(2) call fails.

getPOSIXTimeUSecs :: IO Word64 Source

Return the time as the number of microseconds since the Epoch, 1970-01-01 00:00:00 +0000 (UTC).

Note: this function returns 0 in case the underlying gettimeofday(2) call fails.

See also getPOSIXTimeSecs