Safe Haskell | None |
---|---|
Language | Haskell2010 |
HTTP/2 client library.
Example:
{-# LANGUAGE OverloadedStrings #-} module Main where import qualified Control.Exception as E import Control.Concurrent (forkIO, threadDelay) import qualified Data.ByteString.Char8 as C8 import Network.HTTP.Types import Network.Run.TCP (runTCPClient) -- network-run import Network.HTTP2.Client serverName :: String serverName = "127.0.0.1" main :: IO () main = runTCPClient serverName "80" runHTTP2Client where cliconf = ClientConfig "http" (C8.pack serverName) 20 runHTTP2Client s = E.bracket (allocSimpleConfig s 4096) freeSimpleConfig (\conf -> run cliconf conf client) client sendRequest = do let req = requestNoBody methodGet "/" [] _ <- forkIO $ sendRequest req $ \rsp -> do print rsp getResponseBodyChunk rsp >>= C8.putStrLn sendRequest req $ \rsp -> do threadDelay 100000 print rsp getResponseBodyChunk rsp >>= C8.putStrLn
Synopsis
- run :: ClientConfig -> Config -> Client a -> IO a
- type Scheme = ByteString
- type Authority = ByteString
- data ClientConfig = ClientConfig { }
-
data
Config
=
Config
{
- confWriteBuffer :: Buffer
- confBufferSize :: BufferSize
- confSendAll :: ByteString -> IO ()
- confReadN :: Int -> IO ByteString
- confPositionReadMaker :: PositionReadMaker
- confTimeoutManager :: Manager
- allocSimpleConfig :: Socket -> BufferSize -> IO Config
- freeSimpleConfig :: Config -> IO ()
- type Client a = ( Request -> ( Response -> IO a) -> IO a) -> IO a
- data Request
- requestNoBody :: Method -> Path -> RequestHeaders -> Request
- requestFile :: Method -> Path -> RequestHeaders -> FileSpec -> Request
- requestStreaming :: Method -> Path -> RequestHeaders -> (( Builder -> IO ()) -> IO () -> IO ()) -> Request
- requestBuilder :: Method -> Path -> RequestHeaders -> Builder -> Request
- type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker
-
data
NextTrailersMaker
- = NextTrailersMaker TrailersMaker
- | Trailers [ Header ]
- defaultTrailersMaker :: TrailersMaker
- setRequestTrailersMaker :: Request -> TrailersMaker -> Request
- data Response
- responseStatus :: Response -> Maybe Status
- responseHeaders :: Response -> HeaderTable
- responseBodySize :: Response -> Maybe Int
- getResponseBodyChunk :: Response -> IO ByteString
- getResponseTrailers :: Response -> IO ( Maybe HeaderTable )
- type Method = ByteString
- type Path = ByteString
- data FileSpec = FileSpec FilePath FileOffset ByteCount
- type FileOffset = Int64
- type ByteCount = Int64
- defaultReadN :: Socket -> IORef ( Maybe ByteString ) -> Int -> IO ByteString
- type PositionReadMaker = FilePath -> IO ( PositionRead , Sentinel )
- type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount
- data Sentinel
- defaultPositionReadMaker :: PositionReadMaker
Runner
type Scheme = ByteString Source #
"http" or "https".
type Authority = ByteString Source #
For so-called "Host:" header.
Runner arguments
HTTP/2 configuration.
Config | |
|
allocSimpleConfig :: Socket -> BufferSize -> IO Config Source #
Making simple configuration whose IO is not efficient. A write buffer is allocated internally.
freeSimpleConfig :: Config -> IO () Source #
Deallocating the resource of the simple configuration.
HTTP/2 client
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.
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 -> HeaderTable 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 HeaderTable ) Source #
Reading response trailers.
This function must be called after
getResponseBodyChunk
returns an empty.
Types
type Method = ByteString Source #
HTTP method (flat string type).
type Path = ByteString Source #
Path.
type FileOffset = Int64 Source #
Offset for file.
RecvN
defaultReadN :: Socket -> IORef ( Maybe ByteString ) -> Int -> IO ByteString Source #
Naive implementation for readN.
Position read for files
type PositionReadMaker = FilePath -> IO ( PositionRead , Sentinel ) Source #
Making a position read and its closer.
type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount Source #
Position read for files.
Manipulating a file resource.
defaultPositionReadMaker :: PositionReadMaker Source #
Position read based on
Handle
.