1

I am trying to create a conduit that will stream data from HTTP through a conduit source. Here is what I have so far:

import qualified Network.HTTP.Client.Conduit as CC

getStream :: String -> IO (ConduitM () BS.ByteString IO ())
getStream url = do
  req <- parseUrl url
  return $  CC.withResponse req $ \res -> do
    responseBody res $= (awaitForever $ \bytes -> liftIO $ do
      putStrLn $ "Got " ++ show (BS.length bytes) ++ " but will ignore    them")

But I am getting

No instance for (Control.Monad.Reader.Class.MonadReader env0 IO) …
      arising from a use of ‘CC.withResponse’
    In the expression: CC.withResponse req
    In the second argument of ‘($)’, namely
      ‘CC.withResponse req
       $ \ res
           -> do { responseBody res $= (awaitForever $ \ bytes -> ...) }’
    In a stmt of a 'do' block:
      return
      $ CC.withResponse req
        $ \ res
            -> do { responseBody res $= (awaitForever $ \ bytes -> ...) }

How come a MonadReader is expected? It doesn't make any sense to me.

fakedrake
  • 6,528
  • 8
  • 41
  • 64

1 Answers1

4

How about this variation of the example in the Network.HTTP.Conduit docs:

{-# LANGUAGE OverloadedStrings #-}

module Lib2 () where

import Data.Conduit (($$+-), awaitForever)
import qualified Network.HTTP.Client.Conduit as CC
import Network.HTTP.Conduit (http, tlsManagerSettings, newManager)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Resource (runResourceT)
import Data.Conduit.Binary (sinkFile) -- Exported from the package conduit-extra

main2 :: IO ()
main2 = do
       request <- CC.parseUrl "http://google.com/"
       manager <- newManager tlsManagerSettings
       runResourceT $ do
           response <- http request manager
           CC.responseBody response $$+- (awaitForever $ \x -> liftIO $ putStrLn "Chunk")

Original answer

The return type for getStream is wrong. Try removing the type signature and use FlexibleContexts, e.g.:

{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}

module Lib () where

import Data.Conduit
import qualified Data.ByteString as BS
import qualified Network.HTTP.Client.Conduit as CC
import Control.Monad.IO.Class

getStream url = do
  req <- CC.parseUrl url
  CC.withResponse req $ \res -> do
   CC.responseBody res $= (awaitForever $ \x -> liftIO $ putStrLn "Got a chunk")

And then :t getStream reports:

getStream
  :: (monad-control-1.0.0.4:Control.Monad.Trans.Control.MonadBaseControl
        IO (ConduitM a c m),
      mtl-2.2.1:Control.Monad.Reader.Class.MonadReader env m, MonadIO m,
      CC.HasHttpManager env,
      exceptions-0.8.0.2:Control.Monad.Catch.MonadThrow m) =>
     String -> ConduitM a c m ()

which shows that the return type has the form ConduitM ..., not IO ....

This also shows how MonadReader gets into the picture... The monad m must have access to an HTTP manager through a reader environment as expressed by the following constraints:

CC.HasHttpManager env
MonadReader env m

All this is saying is that m has a reader environment of some type env which itself has a way of accessing an HTTP manager.

In particular, m cannot be just the plain IO monad, which is what the error message is complaining about.

Answer to question in the comments

Here is an example of how to create a Producer from a HTTP response:

{-# LANGUAGE OverloadedStrings #-}

module Lib3 () where

import qualified Data.ByteString as BS
import qualified Network.HTTP.Client.Conduit as CC
import           Network.HTTP.Conduit (http, tlsManagerSettings, newManager)
import qualified Network.HTTP.Client          as Client (httpLbs, responseOpen, responseClose)
import           Data.Conduit (Producer, addCleanup)
import           Data.Conduit (awaitForever, await, ($$))
import qualified Network.HTTP.Client.Conduit  as HCC

import Control.Monad.IO.Class (liftIO, MonadIO)

getStream url = do
  request <- CC.parseUrl url
  manager <- newManager tlsManagerSettings
  response <- Client.responseOpen request manager
  let producer :: Producer IO BS.ByteString
      producer = HCC.bodyReaderSource $ CC.responseBody response
      cleanup _ = do liftIO $ putStrLn "(cleaning up)"; Client.responseClose response
      producerWithCleanup = addCleanup cleanup producer
  return $ response { CC.responseBody = producerWithCleanup }

test = do
  res <- getStream "http://google.com"
  let producer = CC.responseBody res
      consumer = awaitForever $ \_ -> liftIO $ putStrLn "Got a chunk"
  producer $$ consumer
ErikR
  • 51,541
  • 9
  • 73
  • 124
  • Wow that worked better than I expected. Just one question: It seems like the only way to make use of the `Source` stream is to provide a sink as an argument. Is there a way to actually return the `Source` stream, eg. wrapped in `IO`. If not why? Alsy I don't quite get why the `Resouce` monad is necessary. (sorry if it seems obvious I am still trying to wrap my head around `Conduit`) – fakedrake Apr 30 '16 at 09:19
  • Answer updated - see at end. In the `http` function, `ResourceT` is used to call the finalizer for the response. However, the finalizer is also added to the `Producer` conduit (e.g. `producerWithCleanup`) so I don't know if use of `ResourceT` is actually needed - the finalizer seems to get called even if the consumer doesn't consume all of the chunks. – ErikR Apr 30 '16 at 18:21
  • More info about the use of ResourceT here: https://github.com/snoyberg/http-client/issues/194 – ErikR May 01 '16 at 17:46