http-semantics-0.0.0: HTTP senmatics libarry
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.HTTP.Semantics.Client

Synopsis

HTTP client

type Client a = SendRequest -> Aux -> IO a Source #

Client type.

type SendRequest = forall r. Request -> (Response -> IO r) -> IO r Source #

Send a request and receive its response.

Request

data Request Source #

Request from client.

Instances

Instances details
Show Request Source # 
Instance details

Defined in Network.HTTP.Semantics.Client.Internal

Creating request

requestNoBody :: Method -> Path -> RequestHeaders -> Request Source #

Creating request without body.

requestFile :: Method -> Path -> RequestHeaders -> FileSpec -> Request Source #

Creating request with file.

requestStreaming :: Method -> Path -> RequestHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Request Source #

Creating request with streaming.

requestStreamingUnmask :: Method -> Path -> RequestHeaders -> ((forall x. IO x -> IO x) -> (Builder -> IO ()) -> IO () -> IO ()) -> Request Source #

Like requestStreaming, but run the action with exceptions masked

requestBuilder :: Method -> Path -> RequestHeaders -> Builder -> Request Source #

Creating request with builder.

Trailers maker

type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker Source #

Trailers maker. A chunks of the response body is passed with Just. The maker should update internal state with the ByteString and return the next trailers maker. When response body reaches its end, Nothing is passed and the maker should generate trailers. An example:

{-# LANGUAGE BangPatterns #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Crypto.Hash (Context, SHA1) -- cryptonite
import qualified Crypto.Hash as CH

-- Strictness is important for Context.
trailersMaker :: Context SHA1 -> Maybe ByteString -> IO NextTrailersMaker
trailersMaker ctx Nothing = return $ Trailers [("X-SHA1", sha1)]
  where
    !sha1 = C8.pack $ show $ CH.hashFinalize ctx
trailersMaker ctx (Just bs) = return $ NextTrailersMaker $ trailersMaker ctx'
  where
    !ctx' = CH.hashUpdate ctx bs

Usage example:

let h2rsp = responseFile ...
    maker = trailersMaker (CH.hashInit :: Context SHA1)
    h2rsp' = setResponseTrailersMaker h2rsp maker

data NextTrailersMaker Source #

Either the next trailers maker or final trailers.

defaultTrailersMaker :: TrailersMaker Source #

TrailersMake to create no trailers.

Response

data Response Source #

Response from server.

Instances

Instances details
Show Response Source # 
Instance details

Defined in Network.HTTP.Semantics.Client.Internal

Accessing response

responseStatus :: Response -> Maybe Status Source #

Getting the status of a response.

responseHeaders :: Response -> TokenHeaderTable Source #

Getting the headers from a response.

responseBodySize :: Response -> Maybe Int Source #

Getting the body size from a response.

getResponseBodyChunk :: Response -> IO ByteString Source #

Reading a chunk of the response body. An empty ByteString returned when finished.

getResponseTrailers :: Response -> IO (Maybe TokenHeaderTable) Source #

Reading response trailers. This function must be called after getResponseBodyChunk returns an empty.

Aux

data Aux Source #

Additional information.

auxPossibleClientStreams :: Aux -> IO Int Source #

How many streams can be created without blocking.

Types

type Scheme = ByteString Source #

"http" or "https".

type Authority = String Source #

Authority.

type Method = ByteString #

HTTP method (flat ByteString type).

type Path = ByteString Source #

Path.

data FileSpec Source #

File specification.

Instances

Instances details
Show FileSpec Source # 
Instance details

Defined in Network.HTTP.Semantics.Types

Eq FileSpec Source # 
Instance details

Defined in Network.HTTP.Semantics.Types

type FileOffset = Int64 Source #

Offset for file.

type ByteCount = Int64 Source #

How many bytes to read

Reading n bytes

type ReadN = Int -> IO ByteString Source #

Reading n bytes.

defaultReadN :: Socket -> IORef (Maybe ByteString) -> ReadN Source #

Naive implementation for readN.

Position read

type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount Source #

Position read for files.

type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel) Source #

Making a position read and its closer.

data Sentinel Source #

Constructors

Closer (IO ())

Closing a file resource. Its refresher is automatiaclly generated by the internal timer.

Refresher (IO ())

Refreshing a file resource while reading. Closing the file must be done by its own timer or something.