quiver-http-0.0.0.2: Adapter to stream over HTTP(s) with quiver

Safe HaskellNone
LanguageHaskell2010

Control.Quiver.HTTP

Contents

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)

Synopsis

Documentation

Response streaming

streamHTTP Source

Arguments

:: Request

The http-client Request, this need not be streaming.

-> Manager

The http-client Manager, make sure you use the tls manager if you need SSL.

-> (Response () -> Consumer x ByteString IO a)

Your quiver Consumer continuation. Feel free to ignore the Response.

-> 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.