module Network.HTTP.Conduit.Types
( Request (..)
, RequestBody (..)
, ContentType
, Proxy (..)
, HttpException (..)
, Response (..)
, ConnRelease
, ConnReuse (..)
, ManagedConn (..)
, Cookie (..)
, CookieJar (..)
) where
import Data.Int (Int64)
import Data.Word (Word64)
import Data.Typeable (Typeable)
import Blaze.ByteString.Builder
import qualified Data.Conduit as C
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import Data.Time.Clock
import Data.Default
import qualified Data.List as DL
import qualified Network.HTTP.Types as W
import qualified Network.Socket as NS
import Network.Socks5 (SocksConf)
import Control.Exception (Exception, SomeException, IOException)
import Data.Certificate.X509 (X509)
import Network.TLS (PrivateKey)
import Network.HTTP.Conduit.ConnInfo (ConnInfo)
import Network.HTTP.Conduit.Util
import Data.Monoid (Monoid(..))
type ContentType = S.ByteString
data Request m = Request
{ method :: W.Method
, secure :: Bool
, clientCertificates :: [(X509, Maybe PrivateKey)]
, host :: S.ByteString
, port :: Int
, path :: S.ByteString
, queryString :: S.ByteString
, requestHeaders :: W.RequestHeaders
, requestBody :: RequestBody m
, proxy :: Maybe Proxy
, socksProxy :: Maybe SocksConf
, hostAddress :: Maybe NS.HostAddress
, rawBody :: Bool
, decompress :: ContentType -> Bool
, redirectCount :: Int
, checkStatus :: W.Status -> W.ResponseHeaders -> CookieJar -> Maybe SomeException
, responseTimeout :: Maybe Int
, getConnectionWrapper :: forall n. (C.MonadResource n, C.MonadBaseControl IO n)
=> Maybe Int
-> HttpException
-> n (ConnRelease n, ConnInfo, ManagedConn)
-> n (Maybe Int, (ConnRelease n, ConnInfo, ManagedConn))
, cookieJar :: Maybe CookieJar
}
data ConnReuse = Reuse | DontReuse
type ConnRelease m = ConnReuse -> m ()
data ManagedConn = Fresh | Reused
data RequestBody m
= RequestBodyLBS L.ByteString
| RequestBodyBS S.ByteString
| RequestBodyBuilder Int64 Builder
| RequestBodySource Int64 (C.Source m Builder)
| RequestBodySourceChunked (C.Source m Builder)
data Proxy = Proxy
{ proxyHost :: S.ByteString
, proxyPort :: Int
}
deriving (Show, Read, Eq, Ord, Typeable)
data HttpException = StatusCodeException W.Status W.ResponseHeaders CookieJar
| InvalidUrlException String String
| TooManyRedirects [Response L.ByteString]
| UnparseableRedirect (Response L.ByteString)
| TooManyRetries
| HttpParserException String
| HandshakeFailed
| OverlongHeaders
| ResponseTimeout
| FailedConnectionException String Int
| ExpectedBlankAfter100Continue
| InvalidStatusLine S.ByteString
| InvalidHeader S.ByteString
| InternalIOException IOException
| ProxyConnectException S.ByteString Int (Either S.ByteString HttpException)
| NoResponseDataReceived
| TlsException SomeException
| ResponseBodyTooShort Word64 Word64
| InvalidChunkHeaders
deriving (Show, Typeable)
instance Exception HttpException
data Response body = Response
{ responseStatus :: W.Status
, responseVersion :: W.HttpVersion
, responseHeaders :: W.ResponseHeaders
, responseBody :: body
, responseCookieJar :: CookieJar
}
deriving (Show, Eq, Typeable)
data Cookie = Cookie
{ cookie_name :: S.ByteString
, cookie_value :: S.ByteString
, cookie_expiry_time :: UTCTime
, cookie_domain :: S.ByteString
, cookie_path :: S.ByteString
, cookie_creation_time :: UTCTime
, cookie_last_access_time :: UTCTime
, cookie_persistent :: Bool
, cookie_host_only :: Bool
, cookie_secure_only :: Bool
, cookie_http_only :: Bool
}
deriving (Read, Show)
newtype CookieJar = CJ { expose :: [Cookie] }
deriving (Read, Show)
instance Eq Cookie where
(==) a b = name_matches && domain_matches && path_matches
where name_matches = cookie_name a == cookie_name b
domain_matches = cookie_domain a == cookie_domain b
path_matches = cookie_path a == cookie_path b
instance Ord Cookie where
compare c1 c2
| S.length (cookie_path c1) > S.length (cookie_path c2) = LT
| S.length (cookie_path c1) < S.length (cookie_path c2) = GT
| cookie_creation_time c1 > cookie_creation_time c2 = GT
| otherwise = LT
instance Default CookieJar where
def = CJ []
instance Eq CookieJar where
(==) cj1 cj2 = (DL.sort $ expose cj1) == (DL.sort $ expose cj2)
instance Monoid CookieJar where
mempty = def
(CJ a) `mappend` (CJ b) = CJ (DL.nub $ DL.sortBy compare' $ a `mappend` b)
where compare' c1 c2 =
if cookie_creation_time c1 > cookie_creation_time c2
then LT
else GT
instance Functor Response where
fmap f response = response {responseBody = f (responseBody response)}
instance Show (RequestBody m) where
showsPrec d (RequestBodyBS a) =
showParen (d>=11) $ showString "RequestBodyBS " . showsPrec 11 a
showsPrec d (RequestBodyLBS a) =
showParen (d>=11) $ showString "RequestBodyLBS " . showsPrec 11 a
showsPrec d (RequestBodyBuilder l _) =
showParen (d>=11) $ showString "RequestBodyBuilder " . showsPrec 11 l .
showString " " . showString "<Builder>"
showsPrec d (RequestBodySource l _) =
showParen (d>=11) $ showString "RequestBodySource " . showsPrec 11 l .
showString " <Source m Builder>"
showsPrec d (RequestBodySourceChunked _) =
showParen (d>=11) $ showString "RequestBodySource <Source m Builder>"
instance Monad m => Monoid (RequestBody m) where
mempty = RequestBodyLBS mempty
mappend a b =
case (simplify a, simplify b) of
(SBuilder l1 b1, SBuilder l2 b2) -> RequestBodyBuilder (l1 + l2) (b1 <> b2)
(SBuilder l1 b1, SSource l2 s2) -> RequestBodySource (l1 + l2) (C.yield b1 <> s2)
(SSource l1 s1, SBuilder l2 b2) -> RequestBodySource (l1 + l2) (s1 <> C.yield b2)
(SSource l1 s1, SSource l2 s2) -> RequestBodySource (l1 + l2) (s1 <> s2)
(a', b') -> RequestBodySourceChunked (toChunked a' <> toChunked b')
data Simplified m = SBuilder Int64 Builder
| SSource Int64 (C.Source m Builder)
| SChunked (C.Source m Builder)
simplify :: Monad m => RequestBody m -> Simplified m
simplify (RequestBodyBS a) = SBuilder (fromIntegral $ S.length a) (fromByteString a)
simplify (RequestBodyLBS a) = SBuilder (fromIntegral $ L.length a) (fromLazyByteString a)
simplify (RequestBodyBuilder l a) = SBuilder l a
simplify (RequestBodySource l a) = SSource l a
simplify (RequestBodySourceChunked a) = SChunked a
toChunked :: Monad m => Simplified m -> C.Source m Builder
toChunked (SBuilder _ b) = C.yield b
toChunked (SSource _ s) = s
toChunked (SChunked s) = s