| Copyright | © 2016–2017 Mark Karpov Michael Snoyman |
|---|---|
| License | BSD 3 clause |
| Maintainer | Mark Karpov <markkarpov92@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Network.HTTP.Req.Conduit
Description
The module extends functionality available in Network.HTTP.Req with Conduit helpers for streaming big request bodies.
The package re-uses some pieces of code from the http-conduit package,
but not to the extent that depending on that package is reasonable.
- data ReqBodySource = ReqBodySource Int64 (Source IO ByteString)
- httpSource :: MonadResource m => Request -> Manager -> Producer m ByteString
Streaming request bodies
data ReqBodySource Source #
This body option streams contents of request body from the given
Source. The Int64 value is size of the data in bytes.
Using of this body option does not set the Content-Type header.
Constructors
| ReqBodySource Int64 (Source IO ByteString) |
Instances
Streaming response bodies
Streaming response is a bit tricky as acquiring and releasing a resource
(initiating a connection and then closing it in our case) in the context
of conduit streaming requires working with the
ResourceT monad transformer. This does not
play well with the framework req builds.
Essentially there are only two ways to make it work:
- Require that every
MonadHttpmust be an instance ofMonadResource. This obviously makes thereqpackage harder to work with and less user-friendly. Not to mention that most of the time the instance won't be necessary. - Use the
withReqManagerin combination withReturnRequestresponse interpretation to get bothManagerandRequestand then delegate the work to a custom callback.
We go with the second option. Here is an example of how to stream 100000 bytes and save them to a file:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import Control.Exception (throwIO)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Resource (ResourceT)
import Data.Conduit ((=$=), runConduitRes, ConduitM)
import Network.HTTP.Req
import Network.HTTP.Req.Conduit
import qualified Data.Conduit.Binary as CB
instance MonadHttp (ConduitM i o (ResourceT IO)) where
handleHttpException = liftIO . throwIO
main :: IO ()
main = runConduitRes $ do
let size = 100000 :: Int
req' GET (https "httpbin.org" /: "bytes" /~ size) NoReqBody mempty httpSource
=$= CB.sinkFile "my-favorite-file.bin"Arguments
| :: MonadResource m | |
| => Request | Pre-formed |
| -> Manager | Manger to use |
| -> Producer m ByteString | Response body as a |
Perform an HTTP request and get the response as a Producer.