
Hi, I'm trying to use http-enumerator with Twitter's streaming API, which requires OAuth authentication. I was hoping to use the hoauth package for this, but it seems that combining with with http-enumerator is pretty awkward. In principle, it should be straightforward since hoauth defines a HttpClient typeclass, and so I would just need to write an instance for http-enumerator. But in practice it is pretty awkward for a few reasons. One is that both packages define their own Request and Response types - however they are semantically identical, so writing conversion functions is tedious but possible. However, I can't work out how to implement error handling; http-enumerator uses the Control.Failure exception mechanism for returning errors, but I can't work out how to fit that into HttpClient's runClient function. If I use "http" rather than "httpRedirect", I can avoid this to some extent (since http doesn't use Failure HttpException m), but I still can't get it to typecheck. I can get a simple non-streaming instance to typecheck using httpLbs (but again, not httpLbsRedirect): data HttpOAuth = HttpOAuth { } instance O.HttpClient HttpOAuth where runClient c r = (HE.httpLbs . http_cvt_request) r >>= return . cvt where cvt :: HE.Response -> Either String O.Response cvt r@(HE.Response st _ b) | 200 <= st && st < 300 = Right $ http_cvt_response r | otherwise = Left $ "HTTP status" ++ show st However, I can't get the streaming version to type check at all: newtype HttpOAuthStream a m b = HttpOAuthStream { iter :: W.Status -> W.ResponseHeaders -> DE.Iteratee a m b } instance O.HttpClient (HttpOAuthStream a m b) where -- runClient :: (MonadIO m) => c -> Request -> m (Either String Response) runClient c r = liftM cvt $ DE.run $ HE.http (http_cvt_request r) (iter c) cvt :: Show a => Either a HE.Response -> Either String O.Response cvt (Left a) = Left $ show a cvt (Right r) = Right $ http_cvt_response r (Full code below) And since I'm still trying to get my head around enumerators, I may have that aspect of things completely wrong. I haven't even tried running any of this yet, so I don't know if I've made any non-type errors. Am I even barking up the right tree at all? Should I try to be using hoauth this way at all, or should I just hack it up to work within http-enumerator? That seems counter-productive. A general comment: There are many partially functional http packages in hackage. It seems to me that rather than requiring one package be a complete http library, we would get further by allowing different packages to implement different aspects of http, so long as they can all be composed in a reasonable way. At the very least, is it really necessary for hoauth to define its own Request/Response types? Would it be worthwhile trying to define general types which all http packages could use? Is that the goal of Network.Wai? What about the HTTP package? Should I just use that instead? What about Network.Curl? Thanks, J import qualified Data.Enumerator as DE import qualified Data.ByteString.Char8 as C8 import Control.Monad (liftM) import Control.Applicative ((<$>), (<*>), (<|>), empty, pure) import Control.Arrow (first, second, (***)) import qualified Network.OAuth.Consumer as O import qualified Network.OAuth.Http.HttpClient as O import qualified Network.OAuth.Http.Request as O import qualified Network.OAuth.Http.Response as O import qualified Network.HTTP.Enumerator as HE import qualified Network.Wai as W import Data.List (intercalate) import Control.Failure import Control.Exception (SomeException) -- Convert a Network.OAuth.Http.Request into a Network.HTTP.Enumerator.Request -- What. A. Pain. http_cvt_request :: O.Request -> HE.Request http_cvt_request oar = HE.Request method secure host port path query headers body where method = C8.pack . show . O.method $ oar secure = O.ssl oar host = C8.pack . O.host $ oar port = O.port oar path = C8.pack . intercalate "/" $ O.pathComps oar query = packpair <$> (O.toList . O.qString $ oar) headers = (first W.mkCIByteString) . packpair <$> (O.toList . O.reqHeaders $ oar) body = O.reqPayload oar -- Convert a Network.HTTP.Enumerator.Response into a Network.OAuth.Http.Response -- See above. http_cvt_response :: HE.Response -> O.Response http_cvt_response her = O.RspHttp status reason headers payload where status = HE.statusCode her reason = "" -- ? headers = O.fromList $ (unpackpair . first W.ciOriginal) <$> HE.responseHeaders her payload = HE.responseBody her mappair f (a,b) = (f a, f b) packpair = mappair C8.pack unpackpair = mappair C8.unpack newtype HttpOAuthStream a m b = HttpOAuthStream { iter :: W.Status -> W.ResponseHeaders -> DE.Iteratee a m b } instance O.HttpClient (HttpOAuthStream a m b) where -- runClient :: (MonadIO m) => c -> Request -> m (Either String Response) runClient c r = liftM cvt $ DE.run $ HE.http (http_cvt_request r) (iter c) cvt :: Show a => Either a HE.Response -> Either String O.Response cvt (Left a) = Left $ show a cvt (Right r) = Right $ http_cvt_response r data HttpOAuth = HttpOAuth { } instance O.HttpClient HttpOAuth where runClient c r = (HE.httpLbs . http_cvt_request) r >>= return . cvt where cvt :: HE.Response -> Either String O.Response cvt r@(HE.Response st _ b) | 200 <= st && st < 300 = Right $ http_cvt_response r | otherwise = Left $ "HTTP status" ++ show st