| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Quiver.HTTP
Description
Adapter code to interface with the http-client and http-client-tls packages.
With this module you can streaming the request, response, or both.
To stream the request, simply replace your Request requestBody with one
created via either makeChunkedRequestBody or makeFixedRequestBody. You
have the option of either chunked encoding or a fixed size streaming
request. You probably want chunked encoding if that is supported.
To stream the response, use streamHTTP and provide a continuation that
returns a Consumer. Your function will be passed the response, which it is
free to ignore.
To stream the request and response, simply do both.
Below is an example of a streaming response, with a streaming request.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Quiver.HTTP
import Control.Quiver
import Control.Quiver.SP
import Control.Monad
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
main :: IO ()
main = do
req <- parseUrl "http://httpbin.org/post"
let req' = req { method = "POST", requestBody = makeChunkedRequestBody input}
manager <- newManager defaultManagerSettings
streamHTTP req' manager out
where
out :: Response () -> Consumer () ByteString IO ()
out _ = loop
where
loop = do
x <- fetch ()
case x of
Just bs -> do
qlift $ BS.putStrLn bs
loop
Nothing -> return ()
input :: Producer ByteString () IO ()
input = void $ decouple ("chunk1" >:> "chunk2" >:> deliver SPComplete)- module Network.HTTP.Client
- module Network.HTTP.Client.TLS
- streamHTTP :: Request -> Manager -> (Response () -> Consumer x ByteString IO a) -> IO a
- makeChunkedRequestBody :: Producer ByteString () IO () -> RequestBody
- makeFixedRequestBody :: Int64 -> Producer ByteString () IO () -> RequestBody
Documentation
module Network.HTTP.Client
module Network.HTTP.Client.TLS
Response streaming
Arguments
| :: Request | The http-client |
| -> Manager | The http-client |
| -> (Response () -> Consumer x ByteString IO a) | Your quiver |
| -> IO a |
Make a HTTP Request and stream the response.
Request streaming
makeChunkedRequestBody :: Producer ByteString () IO () -> RequestBody Source
Build a RequestBody by chunked transfer encoding a Producer.
Each ByteString produced will be sent as a seperate chunk.
makeFixedRequestBody :: Int64 -> Producer ByteString () IO () -> RequestBody Source
Build a RequestBody by sending a Content-Length header and then
streaming a Producer.
You should probably use makeChunkedRequestBody if it is supported by the
server.