{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.HTTP.Conduit
    ( 
      simpleHttp
    , httpLbs
    , http
      
    , Proxy (..)
    , RequestBody (..)
      
    , Request
    , method
    , secure
    , host
    , port
    , path
    , queryString
    , requestHeaders
    , requestBody
    , proxy
    , hostAddress
    , rawBody
    , decompress
    , redirectCount
#if MIN_VERSION_http_client(0,6,2)
    , shouldStripHeaderOnRedirect
#endif
    , checkResponse
    , responseTimeout
    , cookieJar
    , requestVersion
    , HCC.setQueryString
      
    , requestBodySource
    , requestBodySourceChunked
    , requestBodySourceIO
    , requestBodySourceChunkedIO
      
    , Response
    , responseStatus
    , responseVersion
    , responseHeaders
    , responseBody
    , responseCookieJar
      
    , Manager
    , newManager
    , closeManager
      
    , ManagerSettings
    , tlsManagerSettings
    , mkManagerSettings
    , managerConnCount
    , managerResponseTimeout
    , managerTlsConnection
      
    , HC.ResponseTimeout
    , HC.responseTimeoutMicro
    , HC.responseTimeoutNone
    , HC.responseTimeoutDefault
      
    , Cookie(..)
    , CookieJar
    , createCookieJar
    , destroyCookieJar
      
    , parseUrl
    , parseUrlThrow
    , parseRequest
    , parseRequest_
    , defaultRequest
    , applyBasicAuth
    , addProxy
    , lbsResponse
    , getRedirectedRequest
      
    , alwaysDecompress
    , browserDecompress
      
      
      
    , urlEncodedBody
      
    , HttpException (..)
    , HCC.HttpExceptionContent (..)
    ) where
import qualified Data.ByteString              as S
import qualified Data.ByteString.Lazy         as L
import           Data.Conduit
import qualified Data.Conduit.List            as CL
import           Data.IORef                   (readIORef, writeIORef, newIORef)
import           Data.Int                     (Int64)
import           Control.Applicative          as A ((<$>))
import           Control.Monad.IO.Unlift      (MonadIO (liftIO))
import           Control.Monad.Trans.Resource
import qualified Network.HTTP.Client          as Client (httpLbs, responseOpen, responseClose)
import qualified Network.HTTP.Client          as HC
import qualified Network.HTTP.Client.Conduit  as HCC
import           Network.HTTP.Client.Internal (createCookieJar,
                                               destroyCookieJar)
import           Network.HTTP.Client.Internal (Manager, ManagerSettings,
                                               closeManager, managerConnCount,
                                               managerResponseTimeout,
                                               managerTlsConnection, newManager)
import           Network.HTTP.Client          (parseUrl, parseUrlThrow, urlEncodedBody, applyBasicAuth,
                                               defaultRequest, parseRequest, parseRequest_)
import           Network.HTTP.Client.Internal (addProxy, alwaysDecompress,
                                               browserDecompress)
import           Network.HTTP.Client.Internal (getRedirectedRequest)
import           Network.HTTP.Client.TLS      (mkManagerSettings,
                                               tlsManagerSettings)
import           Network.HTTP.Client.Internal (Cookie (..), CookieJar (..),
                                               HttpException (..), Proxy (..),
                                               Request (..), RequestBody (..),
                                               Response (..))
httpLbs :: MonadIO m => Request -> Manager -> m (Response L.ByteString)
httpLbs :: Request -> Manager -> m (Response ByteString)
httpLbs Request
r Manager
m = IO (Response ByteString) -> m (Response ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Response ByteString) -> m (Response ByteString))
-> IO (Response ByteString) -> m (Response ByteString)
forall a b. (a -> b) -> a -> b
$ Request -> Manager -> IO (Response ByteString)
Client.httpLbs Request
r Manager
m
simpleHttp :: MonadIO m => String -> m L.ByteString
simpleHttp :: String -> m ByteString
simpleHttp String
url = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Manager
man <- ManagerSettings -> IO Manager
newManager ManagerSettings
tlsManagerSettings
    Request
req <- IO Request -> IO Request
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Request -> IO Request) -> IO Request -> IO Request
forall a b. (a -> b) -> a -> b
$ String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
parseUrlThrow String
url
    Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> IO (Response ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
A.<$> Request -> Manager -> IO (Response ByteString)
forall (m :: * -> *).
MonadIO m =>
Request -> Manager -> m (Response ByteString)
httpLbs (Request -> Request
setConnectionClose Request
req) Manager
man
setConnectionClose :: Request -> Request
setConnectionClose :: Request -> Request
setConnectionClose Request
req = Request
req{requestHeaders :: RequestHeaders
requestHeaders = (HeaderName
"Connection", ByteString
"close") (HeaderName, ByteString) -> RequestHeaders -> RequestHeaders
forall a. a -> [a] -> [a]
: Request -> RequestHeaders
requestHeaders Request
req}
lbsResponse :: Monad m
            => Response (ConduitM () S.ByteString m ())
            -> m (Response L.ByteString)
lbsResponse :: Response (ConduitM () ByteString m ()) -> m (Response ByteString)
lbsResponse Response (ConduitM () ByteString m ())
res = do
    [ByteString]
bss <- ConduitT () Void m [ByteString] -> m [ByteString]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void m [ByteString] -> m [ByteString])
-> ConduitT () Void m [ByteString] -> m [ByteString]
forall a b. (a -> b) -> a -> b
$ Response (ConduitM () ByteString m ())
-> ConduitM () ByteString m ()
forall body. Response body -> body
responseBody Response (ConduitM () ByteString m ())
res ConduitM () ByteString m ()
-> ConduitM ByteString Void m [ByteString]
-> ConduitT () Void m [ByteString]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM ByteString Void m [ByteString]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume
    Response ByteString -> m (Response ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Response (ConduitM () ByteString m ())
res
        { responseBody :: ByteString
responseBody = [ByteString] -> ByteString
L.fromChunks [ByteString]
bss
        }
http :: MonadResource m
     => Request
     -> Manager
     -> m (Response (ConduitM i S.ByteString m ()))
http :: Request -> Manager -> m (Response (ConduitM i ByteString m ()))
http Request
req Manager
man = do
    (ReleaseKey
key, Response BodyReader
res) <- IO (Response BodyReader)
-> (Response BodyReader -> IO ())
-> m (ReleaseKey, Response BodyReader)
forall (m :: * -> *) a.
MonadResource m =>
IO a -> (a -> IO ()) -> m (ReleaseKey, a)
allocate (Request -> Manager -> IO (Response BodyReader)
Client.responseOpen Request
req Manager
man) Response BodyReader -> IO ()
forall a. Response a -> IO ()
Client.responseClose
    Response (ConduitM i ByteString m ())
-> m (Response (ConduitM i ByteString m ()))
forall (m :: * -> *) a. Monad m => a -> m a
return Response BodyReader
res { responseBody :: ConduitM i ByteString m ()
responseBody = do
                   BodyReader -> ConduitM i ByteString m ()
forall (m :: * -> *) i.
MonadIO m =>
BodyReader -> ConduitM i ByteString m ()
HCC.bodyReaderSource (BodyReader -> ConduitM i ByteString m ())
-> BodyReader -> ConduitM i ByteString m ()
forall a b. (a -> b) -> a -> b
$ Response BodyReader -> BodyReader
forall body. Response body -> body
responseBody Response BodyReader
res
                   ReleaseKey -> ConduitM i ByteString m ()
forall (m :: * -> *). MonadIO m => ReleaseKey -> m ()
release ReleaseKey
key
               }
requestBodySource :: Int64 -> ConduitM () S.ByteString (ResourceT IO) () -> RequestBody
requestBodySource :: Int64 -> ConduitM () ByteString (ResourceT IO) () -> RequestBody
requestBodySource Int64
size = Int64 -> GivesPopper () -> RequestBody
RequestBodyStream Int64
size (GivesPopper () -> RequestBody)
-> (ConduitM () ByteString (ResourceT IO) () -> GivesPopper ())
-> ConduitM () ByteString (ResourceT IO) ()
-> RequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConduitM () ByteString (ResourceT IO) () -> GivesPopper ()
srcToPopper
requestBodySourceChunked :: ConduitM () S.ByteString (ResourceT IO) () -> RequestBody
requestBodySourceChunked :: ConduitM () ByteString (ResourceT IO) () -> RequestBody
requestBodySourceChunked = GivesPopper () -> RequestBody
RequestBodyStreamChunked (GivesPopper () -> RequestBody)
-> (ConduitM () ByteString (ResourceT IO) () -> GivesPopper ())
-> ConduitM () ByteString (ResourceT IO) ()
-> RequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConduitM () ByteString (ResourceT IO) () -> GivesPopper ()
srcToPopper
srcToPopper :: ConduitM () S.ByteString (ResourceT IO) () -> HCC.GivesPopper ()
srcToPopper :: ConduitM () ByteString (ResourceT IO) () -> GivesPopper ()
srcToPopper ConduitM () ByteString (ResourceT IO) ()
src NeedsPopper ()
f = ResourceT IO () -> IO ()
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT (ResourceT IO () -> IO ()) -> ResourceT IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    (SealedConduitT () ByteString (ResourceT IO) ()
rsrc0, ()) <- ConduitM () ByteString (ResourceT IO) ()
src ConduitM () ByteString (ResourceT IO) ()
-> Sink ByteString (ResourceT IO) ()
-> ResourceT
     IO (SealedConduitT () ByteString (ResourceT IO) (), ())
forall (m :: * -> *) a b.
Monad m =>
Source m a -> Sink a m b -> m (SealedConduitT () a m (), b)
$$+ () -> Sink ByteString (ResourceT IO) ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    IORef (SealedConduitT () ByteString (ResourceT IO) ())
irsrc <- IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
-> ResourceT
     IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
 -> ResourceT
      IO (IORef (SealedConduitT () ByteString (ResourceT IO) ())))
-> IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
-> ResourceT
     IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
forall a b. (a -> b) -> a -> b
$ SealedConduitT () ByteString (ResourceT IO) ()
-> IO (IORef (SealedConduitT () ByteString (ResourceT IO) ()))
forall a. a -> IO (IORef a)
newIORef SealedConduitT () ByteString (ResourceT IO) ()
rsrc0
    InternalState
is <- ResourceT IO InternalState
forall (m :: * -> *). Monad m => ResourceT m InternalState
getInternalState
    let popper :: IO S.ByteString
        popper :: BodyReader
popper = do
            SealedConduitT () ByteString (ResourceT IO) ()
rsrc <- IORef (SealedConduitT () ByteString (ResourceT IO) ())
-> IO (SealedConduitT () ByteString (ResourceT IO) ())
forall a. IORef a -> IO a
readIORef IORef (SealedConduitT () ByteString (ResourceT IO) ())
irsrc
            (SealedConduitT () ByteString (ResourceT IO) ()
rsrc', Maybe ByteString
mres) <- ResourceT
  IO
  (SealedConduitT () ByteString (ResourceT IO) (), Maybe ByteString)
-> InternalState
-> IO
     (SealedConduitT () ByteString (ResourceT IO) (), Maybe ByteString)
forall (m :: * -> *) a. ResourceT m a -> InternalState -> m a
runInternalState (SealedConduitT () ByteString (ResourceT IO) ()
rsrc SealedConduitT () ByteString (ResourceT IO) ()
-> Sink ByteString (ResourceT IO) (Maybe ByteString)
-> ResourceT
     IO
     (SealedConduitT () ByteString (ResourceT IO) (), Maybe ByteString)
forall (m :: * -> *) a b.
Monad m =>
SealedConduitT () a m ()
-> Sink a m b -> m (SealedConduitT () a m (), b)
$$++ Sink ByteString (ResourceT IO) (Maybe ByteString)
forall (m :: * -> *) i. Monad m => Consumer i m (Maybe i)
await) InternalState
is
            IORef (SealedConduitT () ByteString (ResourceT IO) ())
-> SealedConduitT () ByteString (ResourceT IO) () -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (SealedConduitT () ByteString (ResourceT IO) ())
irsrc SealedConduitT () ByteString (ResourceT IO) ()
rsrc'
            case Maybe ByteString
mres of
                Maybe ByteString
Nothing -> ByteString -> BodyReader
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
S.empty
                Just ByteString
bs
                    | ByteString -> Bool
S.null ByteString
bs -> BodyReader
popper
                    | Bool
otherwise -> ByteString -> BodyReader
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
    IO () -> ResourceT IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ResourceT IO ()) -> IO () -> ResourceT IO ()
forall a b. (a -> b) -> a -> b
$ NeedsPopper ()
f BodyReader
popper
requestBodySourceIO :: Int64 -> ConduitM () S.ByteString IO () -> RequestBody
requestBodySourceIO :: Int64 -> ConduitM () ByteString IO () -> RequestBody
requestBodySourceIO = Int64 -> ConduitM () ByteString IO () -> RequestBody
HCC.requestBodySource
requestBodySourceChunkedIO :: ConduitM () S.ByteString IO () -> RequestBody
requestBodySourceChunkedIO :: ConduitM () ByteString IO () -> RequestBody
requestBodySourceChunkedIO = ConduitM () ByteString IO () -> RequestBody
HCC.requestBodySourceChunked