Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Client a = SendRequest -> Aux -> IO a
- type SendRequest = forall r. Request -> (Response -> IO r) -> IO r
- data Request
- requestNoBody :: Method -> Path -> RequestHeaders -> Request
- requestFile :: Method -> Path -> RequestHeaders -> FileSpec -> Request
- requestStreaming :: Method -> Path -> RequestHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Request
- requestStreamingUnmask :: Method -> Path -> RequestHeaders -> ((forall x. IO x -> IO x) -> (Builder -> IO ()) -> IO () -> IO ()) -> Request
- requestBuilder :: Method -> Path -> RequestHeaders -> Builder -> Request
- type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker
- data NextTrailersMaker
- defaultTrailersMaker :: TrailersMaker
- setRequestTrailersMaker :: Request -> TrailersMaker -> Request
- data Response
- responseStatus :: Response -> Maybe Status
- responseHeaders :: Response -> TokenHeaderTable
- responseBodySize :: Response -> Maybe Int
- getResponseBodyChunk :: Response -> IO ByteString
- getResponseTrailers :: Response -> IO (Maybe TokenHeaderTable)
- data Aux
- auxPossibleClientStreams :: Aux -> IO Int
- type Scheme = ByteString
- type Authority = String
- type Method = ByteString
- type Path = ByteString
- data FileSpec = FileSpec FilePath FileOffset ByteCount
- type FileOffset = Int64
- type ByteCount = Int64
- type ReadN = Int -> IO ByteString
- defaultReadN :: Socket -> IORef (Maybe ByteString) -> ReadN
- type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount
- type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel)
- data Sentinel
- defaultPositionReadMaker :: PositionReadMaker
HTTP client
type SendRequest = forall r. Request -> (Response -> IO r) -> IO r Source #
Send a request and receive its response.
Request
Request from client.
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.
setRequestTrailersMaker :: Request -> TrailersMaker -> Request Source #
Setting TrailersMaker
to Response
.
Response
Response from server.
Accessing response
responseHeaders :: Response -> TokenHeaderTable Source #
Getting the headers 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
Types
type Scheme = ByteString Source #
"http" or "https".
type Method = ByteString #
HTTP method (flat ByteString
type).
type Path = ByteString Source #
Path.
type FileOffset = Int64 Source #
Offset for file.
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.
defaultPositionReadMaker :: PositionReadMaker Source #
Position read based on Handle
.