{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.HTTP.Client.Types
( BodyReader
, Connection (..)
, StatusHeaders (..)
, HttpException (..)
, HttpExceptionContent (..)
, unHttpExceptionContentWrapper
, throwHttp
, toHttpException
, Cookie (..)
, equalCookie
, equivCookie
, compareCookies
, CookieJar (..)
, equalCookieJar
, equivCookieJar
, Proxy (..)
, RequestBody (..)
, Popper
, NeedsPopper
, GivesPopper
, Request (..)
, Response (..)
, ResponseClose (..)
, Manager (..)
, HasHttpManager (..)
, ConnsMap (..)
, ManagerSettings (..)
, NonEmptyList (..)
, ConnHost (..)
, ConnKey (..)
, ProxyOverride (..)
, StreamFileStatus (..)
, ResponseTimeout (..)
, ProxySecureMode (..)
) where
import qualified Data.Typeable as T (Typeable)
import Network.HTTP.Types
import Control.Exception (Exception, SomeException, throwIO)
import Data.Word (Word64)
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import Blaze.ByteString.Builder (Builder, fromLazyByteString, fromByteString, toLazyByteString)
import Data.Int (Int64)
import Data.Foldable (Foldable)
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.String (IsString, fromString)
import Data.Time (UTCTime)
import Data.Traversable (Traversable)
import qualified Data.List as DL
import Network.Socket (HostAddress)
import Data.IORef
import qualified Network.Socket as NS
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Text (Text)
import Data.Streaming.Zlib (ZlibException)
import Data.CaseInsensitive as CI
import Data.KeyedPool (KeyedPool)
type BodyReader = IO S.ByteString
data Connection = Connection
{ Connection -> IO ByteString
connectionRead :: IO S.ByteString
, Connection -> ByteString -> IO ()
connectionUnread :: S.ByteString -> IO ()
, Connection -> ByteString -> IO ()
connectionWrite :: S.ByteString -> IO ()
, Connection -> IO ()
connectionClose :: IO ()
}
deriving T.Typeable
data = Status HttpVersion RequestHeaders
deriving (Int -> StatusHeaders -> ShowS
[StatusHeaders] -> ShowS
StatusHeaders -> String
(Int -> StatusHeaders -> ShowS)
-> (StatusHeaders -> String)
-> ([StatusHeaders] -> ShowS)
-> Show StatusHeaders
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StatusHeaders -> ShowS
showsPrec :: Int -> StatusHeaders -> ShowS
$cshow :: StatusHeaders -> String
show :: StatusHeaders -> String
$cshowList :: [StatusHeaders] -> ShowS
showList :: [StatusHeaders] -> ShowS
Show, StatusHeaders -> StatusHeaders -> Bool
(StatusHeaders -> StatusHeaders -> Bool)
-> (StatusHeaders -> StatusHeaders -> Bool) -> Eq StatusHeaders
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StatusHeaders -> StatusHeaders -> Bool
== :: StatusHeaders -> StatusHeaders -> Bool
$c/= :: StatusHeaders -> StatusHeaders -> Bool
/= :: StatusHeaders -> StatusHeaders -> Bool
Eq, Eq StatusHeaders
Eq StatusHeaders =>
(StatusHeaders -> StatusHeaders -> Ordering)
-> (StatusHeaders -> StatusHeaders -> Bool)
-> (StatusHeaders -> StatusHeaders -> Bool)
-> (StatusHeaders -> StatusHeaders -> Bool)
-> (StatusHeaders -> StatusHeaders -> Bool)
-> (StatusHeaders -> StatusHeaders -> StatusHeaders)
-> (StatusHeaders -> StatusHeaders -> StatusHeaders)
-> Ord StatusHeaders
StatusHeaders -> StatusHeaders -> Bool
StatusHeaders -> StatusHeaders -> Ordering
StatusHeaders -> StatusHeaders -> StatusHeaders
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StatusHeaders -> StatusHeaders -> Ordering
compare :: StatusHeaders -> StatusHeaders -> Ordering
$c< :: StatusHeaders -> StatusHeaders -> Bool
< :: StatusHeaders -> StatusHeaders -> Bool
$c<= :: StatusHeaders -> StatusHeaders -> Bool
<= :: StatusHeaders -> StatusHeaders -> Bool
$c> :: StatusHeaders -> StatusHeaders -> Bool
> :: StatusHeaders -> StatusHeaders -> Bool
$c>= :: StatusHeaders -> StatusHeaders -> Bool
>= :: StatusHeaders -> StatusHeaders -> Bool
$cmax :: StatusHeaders -> StatusHeaders -> StatusHeaders
max :: StatusHeaders -> StatusHeaders -> StatusHeaders
$cmin :: StatusHeaders -> StatusHeaders -> StatusHeaders
min :: StatusHeaders -> StatusHeaders -> StatusHeaders
Ord, T.Typeable)
newtype HttpExceptionContentWrapper = HttpExceptionContentWrapper
{ HttpExceptionContentWrapper -> HttpExceptionContent
unHttpExceptionContentWrapper :: HttpExceptionContent
}
deriving (Int -> HttpExceptionContentWrapper -> ShowS
[HttpExceptionContentWrapper] -> ShowS
HttpExceptionContentWrapper -> String
(Int -> HttpExceptionContentWrapper -> ShowS)
-> (HttpExceptionContentWrapper -> String)
-> ([HttpExceptionContentWrapper] -> ShowS)
-> Show HttpExceptionContentWrapper
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HttpExceptionContentWrapper -> ShowS
showsPrec :: Int -> HttpExceptionContentWrapper -> ShowS
$cshow :: HttpExceptionContentWrapper -> String
show :: HttpExceptionContentWrapper -> String
$cshowList :: [HttpExceptionContentWrapper] -> ShowS
showList :: [HttpExceptionContentWrapper] -> ShowS
Show, T.Typeable)
instance Exception HttpExceptionContentWrapper
throwHttp :: HttpExceptionContent -> IO a
throwHttp :: forall a. HttpExceptionContent -> IO a
throwHttp = HttpExceptionContentWrapper -> IO a
forall e a. Exception e => e -> IO a
throwIO (HttpExceptionContentWrapper -> IO a)
-> (HttpExceptionContent -> HttpExceptionContentWrapper)
-> HttpExceptionContent
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HttpExceptionContent -> HttpExceptionContentWrapper
HttpExceptionContentWrapper
toHttpException :: Request -> HttpExceptionContentWrapper -> HttpException
toHttpException :: Request -> HttpExceptionContentWrapper -> HttpException
toHttpException Request
req (HttpExceptionContentWrapper HttpExceptionContent
e) = Request -> HttpExceptionContent -> HttpException
HttpExceptionRequest Request
req HttpExceptionContent
e
data HttpException
= HttpExceptionRequest Request HttpExceptionContent
| InvalidUrlException String String
deriving (Int -> HttpException -> ShowS
[HttpException] -> ShowS
HttpException -> String
(Int -> HttpException -> ShowS)
-> (HttpException -> String)
-> ([HttpException] -> ShowS)
-> Show HttpException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HttpException -> ShowS
showsPrec :: Int -> HttpException -> ShowS
$cshow :: HttpException -> String
show :: HttpException -> String
$cshowList :: [HttpException] -> ShowS
showList :: [HttpException] -> ShowS
Show, T.Typeable)
instance Exception HttpException
data HttpExceptionContent
= StatusCodeException (Response ()) S.ByteString
| TooManyRedirects [Response L.ByteString]
|
| ResponseTimeout
| ConnectionTimeout
| ConnectionFailure SomeException
| InvalidStatusLine S.ByteString
| S.ByteString
| S.ByteString
| InternalException SomeException
| ProxyConnectException S.ByteString Int Status
| NoResponseDataReceived
| TlsNotSupported
| WrongRequestBodyStreamSize Word64 Word64
| ResponseBodyTooShort Word64 Word64
|
|
| InvalidDestinationHost S.ByteString
| HttpZlibException ZlibException
| InvalidProxyEnvironmentVariable Text Text
| ConnectionClosed
| InvalidProxySettings Text
deriving (Int -> HttpExceptionContent -> ShowS
[HttpExceptionContent] -> ShowS
HttpExceptionContent -> String
(Int -> HttpExceptionContent -> ShowS)
-> (HttpExceptionContent -> String)
-> ([HttpExceptionContent] -> ShowS)
-> Show HttpExceptionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HttpExceptionContent -> ShowS
showsPrec :: Int -> HttpExceptionContent -> ShowS
$cshow :: HttpExceptionContent -> String
show :: HttpExceptionContent -> String
$cshowList :: [HttpExceptionContent] -> ShowS
showList :: [HttpExceptionContent] -> ShowS
Show, T.Typeable)
data Cookie = Cookie
{ Cookie -> ByteString
cookie_name :: S.ByteString
, Cookie -> ByteString
cookie_value :: S.ByteString
, Cookie -> UTCTime
cookie_expiry_time :: UTCTime
, Cookie -> ByteString
cookie_domain :: S.ByteString
, Cookie -> ByteString
cookie_path :: S.ByteString
, Cookie -> UTCTime
cookie_creation_time :: UTCTime
, Cookie -> UTCTime
cookie_last_access_time :: UTCTime
, Cookie -> Bool
cookie_persistent :: Bool
, Cookie -> Bool
cookie_host_only :: Bool
, Cookie -> Bool
cookie_secure_only :: Bool
, Cookie -> Bool
cookie_http_only :: Bool
}
deriving (ReadPrec [Cookie]
ReadPrec Cookie
Int -> ReadS Cookie
ReadS [Cookie]
(Int -> ReadS Cookie)
-> ReadS [Cookie]
-> ReadPrec Cookie
-> ReadPrec [Cookie]
-> Read Cookie
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Cookie
readsPrec :: Int -> ReadS Cookie
$creadList :: ReadS [Cookie]
readList :: ReadS [Cookie]
$creadPrec :: ReadPrec Cookie
readPrec :: ReadPrec Cookie
$creadListPrec :: ReadPrec [Cookie]
readListPrec :: ReadPrec [Cookie]
Read, Int -> Cookie -> ShowS
[Cookie] -> ShowS
Cookie -> String
(Int -> Cookie -> ShowS)
-> (Cookie -> String) -> ([Cookie] -> ShowS) -> Show Cookie
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cookie -> ShowS
showsPrec :: Int -> Cookie -> ShowS
$cshow :: Cookie -> String
show :: Cookie -> String
$cshowList :: [Cookie] -> ShowS
showList :: [Cookie] -> ShowS
Show, T.Typeable)
newtype CookieJar = CJ { CookieJar -> [Cookie]
expose :: [Cookie] }
deriving (ReadPrec [CookieJar]
ReadPrec CookieJar
Int -> ReadS CookieJar
ReadS [CookieJar]
(Int -> ReadS CookieJar)
-> ReadS [CookieJar]
-> ReadPrec CookieJar
-> ReadPrec [CookieJar]
-> Read CookieJar
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CookieJar
readsPrec :: Int -> ReadS CookieJar
$creadList :: ReadS [CookieJar]
readList :: ReadS [CookieJar]
$creadPrec :: ReadPrec CookieJar
readPrec :: ReadPrec CookieJar
$creadListPrec :: ReadPrec [CookieJar]
readListPrec :: ReadPrec [CookieJar]
Read, Int -> CookieJar -> ShowS
[CookieJar] -> ShowS
CookieJar -> String
(Int -> CookieJar -> ShowS)
-> (CookieJar -> String)
-> ([CookieJar] -> ShowS)
-> Show CookieJar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CookieJar -> ShowS
showsPrec :: Int -> CookieJar -> ShowS
$cshow :: CookieJar -> String
show :: CookieJar -> String
$cshowList :: [CookieJar] -> ShowS
showList :: [CookieJar] -> ShowS
Show, T.Typeable)
equalCookie :: Cookie -> Cookie -> Bool
equalCookie :: Cookie -> Cookie -> Bool
equalCookie Cookie
a Cookie
b = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and
[ Cookie -> ByteString
cookie_name Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_name Cookie
b
, Cookie -> ByteString
cookie_value Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_value Cookie
b
, Cookie -> UTCTime
cookie_expiry_time Cookie
a UTCTime -> UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_expiry_time Cookie
b
, Cookie -> ByteString
cookie_domain Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_domain Cookie
b
, Cookie -> ByteString
cookie_path Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_path Cookie
b
, Cookie -> UTCTime
cookie_creation_time Cookie
a UTCTime -> UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_creation_time Cookie
b
, Cookie -> UTCTime
cookie_last_access_time Cookie
a UTCTime -> UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_last_access_time Cookie
b
, Cookie -> Bool
cookie_persistent Cookie
a Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_persistent Cookie
b
, Cookie -> Bool
cookie_host_only Cookie
a Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_host_only Cookie
b
, Cookie -> Bool
cookie_secure_only Cookie
a Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_secure_only Cookie
b
, Cookie -> Bool
cookie_http_only Cookie
a Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_http_only Cookie
b
]
equivCookie :: Cookie -> Cookie -> Bool
equivCookie :: Cookie -> Cookie -> Bool
equivCookie Cookie
a Cookie
b = Bool
name_matches Bool -> Bool -> Bool
&& Bool
domain_matches Bool -> Bool -> Bool
&& Bool
path_matches
where name_matches :: Bool
name_matches = Cookie -> ByteString
cookie_name Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_name Cookie
b
domain_matches :: Bool
domain_matches = ByteString -> ByteString
forall s. FoldCase s => s -> s
CI.foldCase (Cookie -> ByteString
cookie_domain Cookie
a) ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString -> ByteString
forall s. FoldCase s => s -> s
CI.foldCase (Cookie -> ByteString
cookie_domain Cookie
b)
path_matches :: Bool
path_matches = Cookie -> ByteString
cookie_path Cookie
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_path Cookie
b
compareCookies :: Cookie -> Cookie -> Ordering
compareCookies :: Cookie -> Cookie -> Ordering
compareCookies Cookie
c1 Cookie
c2
| ByteString -> Int
S.length (Cookie -> ByteString
cookie_path Cookie
c1) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> ByteString -> Int
S.length (Cookie -> ByteString
cookie_path Cookie
c2) = Ordering
LT
| ByteString -> Int
S.length (Cookie -> ByteString
cookie_path Cookie
c1) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< ByteString -> Int
S.length (Cookie -> ByteString
cookie_path Cookie
c2) = Ordering
GT
| Cookie -> UTCTime
cookie_creation_time Cookie
c1 UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
> Cookie -> UTCTime
cookie_creation_time Cookie
c2 = Ordering
GT
| Bool
otherwise = Ordering
LT
equalCookieJar :: CookieJar -> CookieJar -> Bool
equalCookieJar :: CookieJar -> CookieJar -> Bool
equalCookieJar (CJ [Cookie]
cj1) (CJ [Cookie]
cj2) = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool) -> [Bool] -> Bool
forall a b. (a -> b) -> a -> b
$ (Cookie -> Cookie -> Bool) -> [Cookie] -> [Cookie] -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Cookie -> Cookie -> Bool
equalCookie [Cookie]
cj1 [Cookie]
cj2
equivCookieJar :: CookieJar -> CookieJar -> Bool
equivCookieJar :: CookieJar -> CookieJar -> Bool
equivCookieJar CookieJar
cj1 CookieJar
cj2 = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool) -> [Bool] -> Bool
forall a b. (a -> b) -> a -> b
$
(Cookie -> Cookie -> Bool) -> [Cookie] -> [Cookie] -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Cookie -> Cookie -> Bool
equivCookie ((Cookie -> Cookie -> Ordering) -> [Cookie] -> [Cookie]
forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
compareCookies ([Cookie] -> [Cookie]) -> [Cookie] -> [Cookie]
forall a b. (a -> b) -> a -> b
$ CookieJar -> [Cookie]
expose CookieJar
cj1) ((Cookie -> Cookie -> Ordering) -> [Cookie] -> [Cookie]
forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
compareCookies ([Cookie] -> [Cookie]) -> [Cookie] -> [Cookie]
forall a b. (a -> b) -> a -> b
$ CookieJar -> [Cookie]
expose CookieJar
cj2)
instance Semigroup CookieJar where
(CJ [Cookie]
a) <> :: CookieJar -> CookieJar -> CookieJar
<> (CJ [Cookie]
b) = [Cookie] -> CookieJar
CJ ((Cookie -> Cookie -> Bool) -> [Cookie] -> [Cookie]
forall a. (a -> a -> Bool) -> [a] -> [a]
DL.nubBy Cookie -> Cookie -> Bool
equivCookie ([Cookie] -> [Cookie]) -> [Cookie] -> [Cookie]
forall a b. (a -> b) -> a -> b
$ (Cookie -> Cookie -> Ordering) -> [Cookie] -> [Cookie]
forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
mostRecentFirst ([Cookie] -> [Cookie]) -> [Cookie] -> [Cookie]
forall a b. (a -> b) -> a -> b
$ [Cookie]
a [Cookie] -> [Cookie] -> [Cookie]
forall a. Semigroup a => a -> a -> a
<> [Cookie]
b)
where mostRecentFirst :: Cookie -> Cookie -> Ordering
mostRecentFirst Cookie
c1 Cookie
c2 =
if Cookie -> UTCTime
cookie_creation_time Cookie
c1 UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
> Cookie -> UTCTime
cookie_creation_time Cookie
c2
then Ordering
LT
else Ordering
GT
instance Data.Monoid.Monoid CookieJar where
mempty :: CookieJar
mempty = [Cookie] -> CookieJar
CJ []
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
data Proxy = Proxy
{ Proxy -> ByteString
proxyHost :: S.ByteString
, Proxy -> Int
proxyPort :: Int
}
deriving (Int -> Proxy -> ShowS
[Proxy] -> ShowS
Proxy -> String
(Int -> Proxy -> ShowS)
-> (Proxy -> String) -> ([Proxy] -> ShowS) -> Show Proxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Proxy -> ShowS
showsPrec :: Int -> Proxy -> ShowS
$cshow :: Proxy -> String
show :: Proxy -> String
$cshowList :: [Proxy] -> ShowS
showList :: [Proxy] -> ShowS
Show, ReadPrec [Proxy]
ReadPrec Proxy
Int -> ReadS Proxy
ReadS [Proxy]
(Int -> ReadS Proxy)
-> ReadS [Proxy]
-> ReadPrec Proxy
-> ReadPrec [Proxy]
-> Read Proxy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Proxy
readsPrec :: Int -> ReadS Proxy
$creadList :: ReadS [Proxy]
readList :: ReadS [Proxy]
$creadPrec :: ReadPrec Proxy
readPrec :: ReadPrec Proxy
$creadListPrec :: ReadPrec [Proxy]
readListPrec :: ReadPrec [Proxy]
Read, Proxy -> Proxy -> Bool
(Proxy -> Proxy -> Bool) -> (Proxy -> Proxy -> Bool) -> Eq Proxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Proxy -> Proxy -> Bool
== :: Proxy -> Proxy -> Bool
$c/= :: Proxy -> Proxy -> Bool
/= :: Proxy -> Proxy -> Bool
Eq, Eq Proxy
Eq Proxy =>
(Proxy -> Proxy -> Ordering)
-> (Proxy -> Proxy -> Bool)
-> (Proxy -> Proxy -> Bool)
-> (Proxy -> Proxy -> Bool)
-> (Proxy -> Proxy -> Bool)
-> (Proxy -> Proxy -> Proxy)
-> (Proxy -> Proxy -> Proxy)
-> Ord Proxy
Proxy -> Proxy -> Bool
Proxy -> Proxy -> Ordering
Proxy -> Proxy -> Proxy
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Proxy -> Proxy -> Ordering
compare :: Proxy -> Proxy -> Ordering
$c< :: Proxy -> Proxy -> Bool
< :: Proxy -> Proxy -> Bool
$c<= :: Proxy -> Proxy -> Bool
<= :: Proxy -> Proxy -> Bool
$c> :: Proxy -> Proxy -> Bool
> :: Proxy -> Proxy -> Bool
$c>= :: Proxy -> Proxy -> Bool
>= :: Proxy -> Proxy -> Bool
$cmax :: Proxy -> Proxy -> Proxy
max :: Proxy -> Proxy -> Proxy
$cmin :: Proxy -> Proxy -> Proxy
min :: Proxy -> Proxy -> Proxy
Ord, T.Typeable)
data ProxySecureMode =
ProxySecureWithConnect
| ProxySecureWithoutConnect
deriving (Int -> ProxySecureMode -> ShowS
[ProxySecureMode] -> ShowS
ProxySecureMode -> String
(Int -> ProxySecureMode -> ShowS)
-> (ProxySecureMode -> String)
-> ([ProxySecureMode] -> ShowS)
-> Show ProxySecureMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProxySecureMode -> ShowS
showsPrec :: Int -> ProxySecureMode -> ShowS
$cshow :: ProxySecureMode -> String
show :: ProxySecureMode -> String
$cshowList :: [ProxySecureMode] -> ShowS
showList :: [ProxySecureMode] -> ShowS
Show, ReadPrec [ProxySecureMode]
ReadPrec ProxySecureMode
Int -> ReadS ProxySecureMode
ReadS [ProxySecureMode]
(Int -> ReadS ProxySecureMode)
-> ReadS [ProxySecureMode]
-> ReadPrec ProxySecureMode
-> ReadPrec [ProxySecureMode]
-> Read ProxySecureMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ProxySecureMode
readsPrec :: Int -> ReadS ProxySecureMode
$creadList :: ReadS [ProxySecureMode]
readList :: ReadS [ProxySecureMode]
$creadPrec :: ReadPrec ProxySecureMode
readPrec :: ReadPrec ProxySecureMode
$creadListPrec :: ReadPrec [ProxySecureMode]
readListPrec :: ReadPrec [ProxySecureMode]
Read, ProxySecureMode -> ProxySecureMode -> Bool
(ProxySecureMode -> ProxySecureMode -> Bool)
-> (ProxySecureMode -> ProxySecureMode -> Bool)
-> Eq ProxySecureMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProxySecureMode -> ProxySecureMode -> Bool
== :: ProxySecureMode -> ProxySecureMode -> Bool
$c/= :: ProxySecureMode -> ProxySecureMode -> Bool
/= :: ProxySecureMode -> ProxySecureMode -> Bool
Eq, Eq ProxySecureMode
Eq ProxySecureMode =>
(ProxySecureMode -> ProxySecureMode -> Ordering)
-> (ProxySecureMode -> ProxySecureMode -> Bool)
-> (ProxySecureMode -> ProxySecureMode -> Bool)
-> (ProxySecureMode -> ProxySecureMode -> Bool)
-> (ProxySecureMode -> ProxySecureMode -> Bool)
-> (ProxySecureMode -> ProxySecureMode -> ProxySecureMode)
-> (ProxySecureMode -> ProxySecureMode -> ProxySecureMode)
-> Ord ProxySecureMode
ProxySecureMode -> ProxySecureMode -> Bool
ProxySecureMode -> ProxySecureMode -> Ordering
ProxySecureMode -> ProxySecureMode -> ProxySecureMode
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ProxySecureMode -> ProxySecureMode -> Ordering
compare :: ProxySecureMode -> ProxySecureMode -> Ordering
$c< :: ProxySecureMode -> ProxySecureMode -> Bool
< :: ProxySecureMode -> ProxySecureMode -> Bool
$c<= :: ProxySecureMode -> ProxySecureMode -> Bool
<= :: ProxySecureMode -> ProxySecureMode -> Bool
$c> :: ProxySecureMode -> ProxySecureMode -> Bool
> :: ProxySecureMode -> ProxySecureMode -> Bool
$c>= :: ProxySecureMode -> ProxySecureMode -> Bool
>= :: ProxySecureMode -> ProxySecureMode -> Bool
$cmax :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
max :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
$cmin :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
min :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
Ord, T.Typeable)
data RequestBody
= RequestBodyLBS L.ByteString
| RequestBodyBS S.ByteString
| RequestBodyBuilder Int64 Builder
| RequestBodyStream Int64 (GivesPopper ())
| RequestBodyStreamChunked (GivesPopper ())
| RequestBodyIO (IO RequestBody)
deriving T.Typeable
instance IsString RequestBody where
fromString :: String -> RequestBody
fromString String
str = ByteString -> RequestBody
RequestBodyBS (String -> ByteString
forall a. IsString a => String -> a
fromString String
str)
instance Monoid RequestBody where
mempty :: RequestBody
mempty = ByteString -> RequestBody
RequestBodyBS ByteString
S.empty
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
instance Semigroup RequestBody where
RequestBody
x0 <> :: RequestBody -> RequestBody -> RequestBody
<> RequestBody
y0 =
case (RequestBody
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
simplify RequestBody
x0, RequestBody
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
simplify RequestBody
y0) of
(Left (Int64
i, Builder
x), Left (Int64
j, Builder
y)) -> Int64 -> Builder -> RequestBody
RequestBodyBuilder (Int64
i Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
j) (Builder
x Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
y)
(Left (Int64, Builder)
x, Right (Maybe Int64, GivesPopper ())
y) -> (Maybe Int64, GivesPopper ())
-> (Maybe Int64, GivesPopper ()) -> RequestBody
combine ((Int64, Builder) -> (Maybe Int64, GivesPopper ())
builderToStream (Int64, Builder)
x) (Maybe Int64, GivesPopper ())
y
(Right (Maybe Int64, GivesPopper ())
x, Left (Int64, Builder)
y) -> (Maybe Int64, GivesPopper ())
-> (Maybe Int64, GivesPopper ()) -> RequestBody
combine (Maybe Int64, GivesPopper ())
x ((Int64, Builder) -> (Maybe Int64, GivesPopper ())
builderToStream (Int64, Builder)
y)
(Right (Maybe Int64, GivesPopper ())
x, Right (Maybe Int64, GivesPopper ())
y) -> (Maybe Int64, GivesPopper ())
-> (Maybe Int64, GivesPopper ()) -> RequestBody
combine (Maybe Int64, GivesPopper ())
x (Maybe Int64, GivesPopper ())
y
where
combine :: (Maybe Int64, GivesPopper ())
-> (Maybe Int64, GivesPopper ()) -> RequestBody
combine (Just Int64
i, GivesPopper ()
x) (Just Int64
j, GivesPopper ()
y) = Int64 -> GivesPopper () -> RequestBody
RequestBodyStream (Int64
i Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
j) (GivesPopper () -> GivesPopper () -> GivesPopper ()
combine' GivesPopper ()
x GivesPopper ()
y)
combine (Maybe Int64
_, GivesPopper ()
x) (Maybe Int64
_, GivesPopper ()
y) = GivesPopper () -> RequestBody
RequestBodyStreamChunked (GivesPopper () -> GivesPopper () -> GivesPopper ()
combine' GivesPopper ()
x GivesPopper ()
y)
combine' :: GivesPopper () -> GivesPopper () -> GivesPopper ()
combine' :: GivesPopper () -> GivesPopper () -> GivesPopper ()
combine' GivesPopper ()
x GivesPopper ()
y NeedsPopper ()
f = GivesPopper ()
x GivesPopper () -> GivesPopper ()
forall a b. (a -> b) -> a -> b
$ \IO ByteString
x' -> GivesPopper ()
y GivesPopper () -> GivesPopper ()
forall a b. (a -> b) -> a -> b
$ \IO ByteString
y' -> IO ByteString -> IO ByteString -> GivesPopper ()
combine'' IO ByteString
x' IO ByteString
y' NeedsPopper ()
f
combine'' :: Popper -> Popper -> NeedsPopper () -> IO ()
combine'' :: IO ByteString -> IO ByteString -> GivesPopper ()
combine'' IO ByteString
x IO ByteString
y NeedsPopper ()
f = do
IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate <- Either (IO ByteString, IO ByteString) (IO ByteString)
-> IO
(IORef (Either (IO ByteString, IO ByteString) (IO ByteString)))
forall a. a -> IO (IORef a)
newIORef (Either (IO ByteString, IO ByteString) (IO ByteString)
-> IO
(IORef (Either (IO ByteString, IO ByteString) (IO ByteString))))
-> Either (IO ByteString, IO ByteString) (IO ByteString)
-> IO
(IORef (Either (IO ByteString, IO ByteString) (IO ByteString)))
forall a b. (a -> b) -> a -> b
$ (IO ByteString, IO ByteString)
-> Either (IO ByteString, IO ByteString) (IO ByteString)
forall a b. a -> Either a b
Left (IO ByteString
x, IO ByteString
y)
NeedsPopper ()
f NeedsPopper () -> NeedsPopper ()
forall a b. (a -> b) -> a -> b
$ IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
-> IO ByteString
go IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate
go :: IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
-> IO ByteString
go IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate = do
Either (IO ByteString, IO ByteString) (IO ByteString)
state <- IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
-> IO (Either (IO ByteString, IO ByteString) (IO ByteString))
forall a. IORef a -> IO a
readIORef IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate
case Either (IO ByteString, IO ByteString) (IO ByteString)
state of
Left (IO ByteString
x, IO ByteString
y) -> do
ByteString
bs <- IO ByteString
x
if ByteString -> Bool
S.null ByteString
bs
then do
IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
-> Either (IO ByteString, IO ByteString) (IO ByteString) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate (Either (IO ByteString, IO ByteString) (IO ByteString) -> IO ())
-> Either (IO ByteString, IO ByteString) (IO ByteString) -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ByteString
-> Either (IO ByteString, IO ByteString) (IO ByteString)
forall a b. b -> Either a b
Right IO ByteString
y
IO ByteString
y
else ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
Right IO ByteString
y -> IO ByteString
y
simplify :: RequestBody -> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
simplify :: RequestBody
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
simplify (RequestBodyLBS ByteString
lbs) = (Int64, Builder)
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a b. a -> Either a b
Left (ByteString -> Int64
L.length ByteString
lbs, ByteString -> Builder
fromLazyByteString ByteString
lbs)
simplify (RequestBodyBS ByteString
bs) = (Int64, Builder)
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a b. a -> Either a b
Left (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
S.length ByteString
bs, ByteString -> Builder
fromByteString ByteString
bs)
simplify (RequestBodyBuilder Int64
len Builder
b) = (Int64, Builder)
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a b. a -> Either a b
Left (Int64
len, Builder
b)
simplify (RequestBodyStream Int64
i GivesPopper ()
gp) = (Maybe Int64, GivesPopper ())
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a b. b -> Either a b
Right (Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
i, GivesPopper ()
gp)
simplify (RequestBodyStreamChunked GivesPopper ()
gp) = (Maybe Int64, GivesPopper ())
-> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a b. b -> Either a b
Right (Maybe Int64
forall a. Maybe a
Nothing, GivesPopper ()
gp)
simplify (RequestBodyIO IO RequestBody
_mbody) = String -> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
forall a. HasCallStack => String -> a
error String
"FIXME No support for Monoid on RequestBodyIO"
builderToStream :: (Int64, Builder) -> (Maybe Int64, GivesPopper ())
builderToStream :: (Int64, Builder) -> (Maybe Int64, GivesPopper ())
builderToStream (Int64
len, Builder
builder) =
(Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
len, GivesPopper ()
forall {b}. (IO ByteString -> IO b) -> IO b
gp)
where
gp :: (IO ByteString -> IO b) -> IO b
gp IO ByteString -> IO b
np = do
IORef [ByteString]
ibss <- [ByteString] -> IO (IORef [ByteString])
forall a. a -> IO (IORef a)
newIORef ([ByteString] -> IO (IORef [ByteString]))
-> [ByteString] -> IO (IORef [ByteString])
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
L.toChunks (ByteString -> [ByteString]) -> ByteString -> [ByteString]
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
toLazyByteString Builder
builder
IO ByteString -> IO b
np (IO ByteString -> IO b) -> IO ByteString -> IO b
forall a b. (a -> b) -> a -> b
$ do
[ByteString]
bss <- IORef [ByteString] -> IO [ByteString]
forall a. IORef a -> IO a
readIORef IORef [ByteString]
ibss
case [ByteString]
bss of
[] -> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
S.empty
ByteString
bs:[ByteString]
bss' -> do
IORef [ByteString] -> [ByteString] -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef [ByteString]
ibss [ByteString]
bss'
ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
type Popper = IO S.ByteString
type NeedsPopper a = Popper -> IO a
type GivesPopper a = NeedsPopper a -> IO a
data Request = Request
{ Request -> ByteString
method :: Method
, Request -> Bool
secure :: Bool
, Request -> ByteString
host :: S.ByteString
, Request -> Int
port :: Int
, Request -> ByteString
path :: S.ByteString
, Request -> ByteString
queryString :: S.ByteString
, :: RequestHeaders
, Request -> RequestBody
requestBody :: RequestBody
, Request -> Maybe Proxy
proxy :: Maybe Proxy
, Request -> Maybe HostAddress
hostAddress :: Maybe HostAddress
, Request -> Bool
rawBody :: Bool
, Request -> ByteString -> Bool
decompress :: S.ByteString -> Bool
, Request -> Int
redirectCount :: Int
, Request -> Request -> Response (IO ByteString) -> IO ()
checkResponse :: Request -> Response BodyReader -> IO ()
, Request -> ResponseTimeout
responseTimeout :: ResponseTimeout
, Request -> Maybe CookieJar
cookieJar :: Maybe CookieJar
, Request -> HttpVersion
requestVersion :: HttpVersion
, Request -> SomeException -> IO ()
onRequestBodyException :: SomeException -> IO ()
, Request -> Maybe Manager
requestManagerOverride :: Maybe Manager
, :: HeaderName -> Bool
, Request -> ProxySecureMode
proxySecureMode :: ProxySecureMode
, :: Set.Set HeaderName
}
deriving T.Typeable
data ResponseTimeout
= ResponseTimeoutMicro !Int
| ResponseTimeoutNone
| ResponseTimeoutDefault
deriving (ResponseTimeout -> ResponseTimeout -> Bool
(ResponseTimeout -> ResponseTimeout -> Bool)
-> (ResponseTimeout -> ResponseTimeout -> Bool)
-> Eq ResponseTimeout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseTimeout -> ResponseTimeout -> Bool
== :: ResponseTimeout -> ResponseTimeout -> Bool
$c/= :: ResponseTimeout -> ResponseTimeout -> Bool
/= :: ResponseTimeout -> ResponseTimeout -> Bool
Eq, Int -> ResponseTimeout -> ShowS
[ResponseTimeout] -> ShowS
ResponseTimeout -> String
(Int -> ResponseTimeout -> ShowS)
-> (ResponseTimeout -> String)
-> ([ResponseTimeout] -> ShowS)
-> Show ResponseTimeout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseTimeout -> ShowS
showsPrec :: Int -> ResponseTimeout -> ShowS
$cshow :: ResponseTimeout -> String
show :: ResponseTimeout -> String
$cshowList :: [ResponseTimeout] -> ShowS
showList :: [ResponseTimeout] -> ShowS
Show)
instance Show Request where
show :: Request -> String
show Request
x = [String] -> String
unlines
[ String
"Request {"
, String
" host = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (Request -> ByteString
host Request
x)
, String
" port = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Request -> Int
port Request
x)
, String
" secure = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> String
forall a. Show a => a -> String
show (Request -> Bool
secure Request
x)
, String
" requestHeaders = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ RequestHeaders -> String
forall a. Show a => a -> String
show (((HeaderName, ByteString) -> (HeaderName, ByteString))
-> RequestHeaders -> RequestHeaders
forall a b. (a -> b) -> [a] -> [b]
DL.map (Set HeaderName
-> (HeaderName, ByteString) -> (HeaderName, ByteString)
redactSensitiveHeader (Set HeaderName
-> (HeaderName, ByteString) -> (HeaderName, ByteString))
-> Set HeaderName
-> (HeaderName, ByteString)
-> (HeaderName, ByteString)
forall a b. (a -> b) -> a -> b
$ Request -> Set HeaderName
redactHeaders Request
x) (Request -> RequestHeaders
requestHeaders Request
x))
, String
" path = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (Request -> ByteString
path Request
x)
, String
" queryString = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (Request -> ByteString
queryString Request
x)
, String
" method = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (Request -> ByteString
method Request
x)
, String
" proxy = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Proxy -> String
forall a. Show a => a -> String
show (Request -> Maybe Proxy
proxy Request
x)
, String
" rawBody = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> String
forall a. Show a => a -> String
show (Request -> Bool
rawBody Request
x)
, String
" redirectCount = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Request -> Int
redirectCount Request
x)
, String
" responseTimeout = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ResponseTimeout -> String
forall a. Show a => a -> String
show (Request -> ResponseTimeout
responseTimeout Request
x)
, String
" requestVersion = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ HttpVersion -> String
forall a. Show a => a -> String
show (Request -> HttpVersion
requestVersion Request
x)
, String
" proxySecureMode = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ProxySecureMode -> String
forall a. Show a => a -> String
show (Request -> ProxySecureMode
proxySecureMode Request
x)
, String
"}"
]
redactSensitiveHeader :: Set.Set HeaderName -> Header -> Header
Set HeaderName
toRedact h :: (HeaderName, ByteString)
h@(HeaderName
name, ByteString
_) =
if HeaderName
name HeaderName -> Set HeaderName -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set HeaderName
toRedact
then (HeaderName
name, ByteString
"<REDACTED>")
else (HeaderName, ByteString)
h
data Response body = Response
{ forall body. Response body -> Status
responseStatus :: Status
, forall body. Response body -> HttpVersion
responseVersion :: HttpVersion
, :: ResponseHeaders
, forall body. Response body -> body
responseBody :: body
, forall body. Response body -> CookieJar
responseCookieJar :: CookieJar
, forall body. Response body -> ResponseClose
responseClose' :: ResponseClose
, forall body. Response body -> Request
responseOriginalRequest :: Request
}
deriving (Int -> Response body -> ShowS
[Response body] -> ShowS
Response body -> String
(Int -> Response body -> ShowS)
-> (Response body -> String)
-> ([Response body] -> ShowS)
-> Show (Response body)
forall body. Show body => Int -> Response body -> ShowS
forall body. Show body => [Response body] -> ShowS
forall body. Show body => Response body -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall body. Show body => Int -> Response body -> ShowS
showsPrec :: Int -> Response body -> ShowS
$cshow :: forall body. Show body => Response body -> String
show :: Response body -> String
$cshowList :: forall body. Show body => [Response body] -> ShowS
showList :: [Response body] -> ShowS
Show, T.Typeable, (forall a b. (a -> b) -> Response a -> Response b)
-> (forall a b. a -> Response b -> Response a) -> Functor Response
forall a b. a -> Response b -> Response a
forall a b. (a -> b) -> Response a -> Response b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Response a -> Response b
fmap :: forall a b. (a -> b) -> Response a -> Response b
$c<$ :: forall a b. a -> Response b -> Response a
<$ :: forall a b. a -> Response b -> Response a
Functor, (forall m. Monoid m => Response m -> m)
-> (forall m a. Monoid m => (a -> m) -> Response a -> m)
-> (forall m a. Monoid m => (a -> m) -> Response a -> m)
-> (forall a b. (a -> b -> b) -> b -> Response a -> b)
-> (forall a b. (a -> b -> b) -> b -> Response a -> b)
-> (forall b a. (b -> a -> b) -> b -> Response a -> b)
-> (forall b a. (b -> a -> b) -> b -> Response a -> b)
-> (forall a. (a -> a -> a) -> Response a -> a)
-> (forall a. (a -> a -> a) -> Response a -> a)
-> (forall a. Response a -> [a])
-> (forall a. Response a -> Bool)
-> (forall a. Response a -> Int)
-> (forall a. Eq a => a -> Response a -> Bool)
-> (forall a. Ord a => Response a -> a)
-> (forall a. Ord a => Response a -> a)
-> (forall a. Num a => Response a -> a)
-> (forall a. Num a => Response a -> a)
-> Foldable Response
forall a. Eq a => a -> Response a -> Bool
forall a. Num a => Response a -> a
forall a. Ord a => Response a -> a
forall m. Monoid m => Response m -> m
forall a. Response a -> Bool
forall a. Response a -> Int
forall a. Response a -> [a]
forall a. (a -> a -> a) -> Response a -> a
forall m a. Monoid m => (a -> m) -> Response a -> m
forall b a. (b -> a -> b) -> b -> Response a -> b
forall a b. (a -> b -> b) -> b -> Response a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Response m -> m
fold :: forall m. Monoid m => Response m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Response a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Response a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Response a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Response a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Response a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Response a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Response a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Response a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Response a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Response a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Response a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Response a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Response a -> a
foldr1 :: forall a. (a -> a -> a) -> Response a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Response a -> a
foldl1 :: forall a. (a -> a -> a) -> Response a -> a
$ctoList :: forall a. Response a -> [a]
toList :: forall a. Response a -> [a]
$cnull :: forall a. Response a -> Bool
null :: forall a. Response a -> Bool
$clength :: forall a. Response a -> Int
length :: forall a. Response a -> Int
$celem :: forall a. Eq a => a -> Response a -> Bool
elem :: forall a. Eq a => a -> Response a -> Bool
$cmaximum :: forall a. Ord a => Response a -> a
maximum :: forall a. Ord a => Response a -> a
$cminimum :: forall a. Ord a => Response a -> a
minimum :: forall a. Ord a => Response a -> a
$csum :: forall a. Num a => Response a -> a
sum :: forall a. Num a => Response a -> a
$cproduct :: forall a. Num a => Response a -> a
product :: forall a. Num a => Response a -> a
Data.Foldable.Foldable, Functor Response
Foldable Response
(Functor Response, Foldable Response) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Response a -> f (Response b))
-> (forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b))
-> (forall (m :: * -> *) a.
Monad m =>
Response (m a) -> m (Response a))
-> Traversable Response
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Response (m a) -> m (Response a)
forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Response a -> f (Response b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Response a -> f (Response b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Response a -> f (Response b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b)
$csequence :: forall (m :: * -> *) a. Monad m => Response (m a) -> m (Response a)
sequence :: forall (m :: * -> *) a. Monad m => Response (m a) -> m (Response a)
Data.Traversable.Traversable)
newtype ResponseClose = ResponseClose { ResponseClose -> IO ()
runResponseClose :: IO () }
deriving T.Typeable
instance Show ResponseClose where
show :: ResponseClose -> String
show ResponseClose
_ = String
"ResponseClose"
data ManagerSettings = ManagerSettings
{ ManagerSettings -> Int
managerConnCount :: Int
, ManagerSettings
-> IO (Maybe HostAddress -> String -> Int -> IO Connection)
managerRawConnection :: IO (Maybe NS.HostAddress -> String -> Int -> IO Connection)
, ManagerSettings
-> IO (Maybe HostAddress -> String -> Int -> IO Connection)
managerTlsConnection :: IO (Maybe NS.HostAddress -> String -> Int -> IO Connection)
, ManagerSettings
-> IO
(ByteString
-> (Connection -> IO ())
-> String
-> Maybe HostAddress
-> String
-> Int
-> IO Connection)
managerTlsProxyConnection :: IO (S.ByteString -> (Connection -> IO ()) -> String -> Maybe NS.HostAddress -> String -> Int -> IO Connection)
, ManagerSettings -> ResponseTimeout
managerResponseTimeout :: ResponseTimeout
, ManagerSettings -> SomeException -> Bool
managerRetryableException :: SomeException -> Bool
, ManagerSettings -> forall a. Request -> IO a -> IO a
managerWrapException :: forall a. Request -> IO a -> IO a
, ManagerSettings -> Int
managerIdleConnectionCount :: Int
, ManagerSettings -> Request -> IO Request
managerModifyRequest :: Request -> IO Request
, ManagerSettings
-> Response (IO ByteString) -> IO (Response (IO ByteString))
managerModifyResponse :: Response BodyReader -> IO (Response BodyReader)
, ManagerSettings -> ProxyOverride
managerProxyInsecure :: ProxyOverride
, ManagerSettings -> ProxyOverride
managerProxySecure :: ProxyOverride
}
deriving T.Typeable
newtype ProxyOverride = ProxyOverride
{ ProxyOverride -> Bool -> IO (Request -> Request)
runProxyOverride :: Bool -> IO (Request -> Request)
}
deriving T.Typeable
data Manager = Manager
{ Manager -> KeyedPool ConnKey Connection
mConns :: KeyedPool ConnKey Connection
, Manager -> ResponseTimeout
mResponseTimeout :: ResponseTimeout
, Manager -> SomeException -> Bool
mRetryableException :: SomeException -> Bool
, Manager -> forall a. Request -> IO a -> IO a
mWrapException :: forall a. Request -> IO a -> IO a
, Manager -> Request -> IO Request
mModifyRequest :: Request -> IO Request
, Manager -> Request -> Request
mSetProxy :: Request -> Request
, Manager
-> Response (IO ByteString) -> IO (Response (IO ByteString))
mModifyResponse :: Response BodyReader -> IO (Response BodyReader)
}
deriving T.Typeable
class HasHttpManager a where
getHttpManager :: a -> Manager
instance HasHttpManager Manager where
getHttpManager :: Manager -> Manager
getHttpManager = Manager -> Manager
forall a. a -> a
id
data ConnsMap
= ManagerClosed
| ManagerOpen {-# UNPACK #-} !Int !(Map.Map ConnKey (NonEmptyList Connection))
data NonEmptyList a =
One a UTCTime |
Cons a Int UTCTime (NonEmptyList a)
deriving T.Typeable
data ConnHost =
HostName Text |
HostAddress NS.HostAddress
deriving (ConnHost -> ConnHost -> Bool
(ConnHost -> ConnHost -> Bool)
-> (ConnHost -> ConnHost -> Bool) -> Eq ConnHost
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnHost -> ConnHost -> Bool
== :: ConnHost -> ConnHost -> Bool
$c/= :: ConnHost -> ConnHost -> Bool
/= :: ConnHost -> ConnHost -> Bool
Eq, Int -> ConnHost -> ShowS
[ConnHost] -> ShowS
ConnHost -> String
(Int -> ConnHost -> ShowS)
-> (ConnHost -> String) -> ([ConnHost] -> ShowS) -> Show ConnHost
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnHost -> ShowS
showsPrec :: Int -> ConnHost -> ShowS
$cshow :: ConnHost -> String
show :: ConnHost -> String
$cshowList :: [ConnHost] -> ShowS
showList :: [ConnHost] -> ShowS
Show, Eq ConnHost
Eq ConnHost =>
(ConnHost -> ConnHost -> Ordering)
-> (ConnHost -> ConnHost -> Bool)
-> (ConnHost -> ConnHost -> Bool)
-> (ConnHost -> ConnHost -> Bool)
-> (ConnHost -> ConnHost -> Bool)
-> (ConnHost -> ConnHost -> ConnHost)
-> (ConnHost -> ConnHost -> ConnHost)
-> Ord ConnHost
ConnHost -> ConnHost -> Bool
ConnHost -> ConnHost -> Ordering
ConnHost -> ConnHost -> ConnHost
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConnHost -> ConnHost -> Ordering
compare :: ConnHost -> ConnHost -> Ordering
$c< :: ConnHost -> ConnHost -> Bool
< :: ConnHost -> ConnHost -> Bool
$c<= :: ConnHost -> ConnHost -> Bool
<= :: ConnHost -> ConnHost -> Bool
$c> :: ConnHost -> ConnHost -> Bool
> :: ConnHost -> ConnHost -> Bool
$c>= :: ConnHost -> ConnHost -> Bool
>= :: ConnHost -> ConnHost -> Bool
$cmax :: ConnHost -> ConnHost -> ConnHost
max :: ConnHost -> ConnHost -> ConnHost
$cmin :: ConnHost -> ConnHost -> ConnHost
min :: ConnHost -> ConnHost -> ConnHost
Ord, T.Typeable)
data ConnKey
= CKRaw (Maybe HostAddress) {-# UNPACK #-} !S.ByteString !Int
| CKSecure (Maybe HostAddress) {-# UNPACK #-} !S.ByteString !Int
| CKProxy
{-# UNPACK #-} !S.ByteString
!Int
(Maybe S.ByteString)
{-# UNPACK #-} !S.ByteString
!Int
deriving (ConnKey -> ConnKey -> Bool
(ConnKey -> ConnKey -> Bool)
-> (ConnKey -> ConnKey -> Bool) -> Eq ConnKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnKey -> ConnKey -> Bool
== :: ConnKey -> ConnKey -> Bool
$c/= :: ConnKey -> ConnKey -> Bool
/= :: ConnKey -> ConnKey -> Bool
Eq, Int -> ConnKey -> ShowS
[ConnKey] -> ShowS
ConnKey -> String
(Int -> ConnKey -> ShowS)
-> (ConnKey -> String) -> ([ConnKey] -> ShowS) -> Show ConnKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnKey -> ShowS
showsPrec :: Int -> ConnKey -> ShowS
$cshow :: ConnKey -> String
show :: ConnKey -> String
$cshowList :: [ConnKey] -> ShowS
showList :: [ConnKey] -> ShowS
Show, Eq ConnKey
Eq ConnKey =>
(ConnKey -> ConnKey -> Ordering)
-> (ConnKey -> ConnKey -> Bool)
-> (ConnKey -> ConnKey -> Bool)
-> (ConnKey -> ConnKey -> Bool)
-> (ConnKey -> ConnKey -> Bool)
-> (ConnKey -> ConnKey -> ConnKey)
-> (ConnKey -> ConnKey -> ConnKey)
-> Ord ConnKey
ConnKey -> ConnKey -> Bool
ConnKey -> ConnKey -> Ordering
ConnKey -> ConnKey -> ConnKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConnKey -> ConnKey -> Ordering
compare :: ConnKey -> ConnKey -> Ordering
$c< :: ConnKey -> ConnKey -> Bool
< :: ConnKey -> ConnKey -> Bool
$c<= :: ConnKey -> ConnKey -> Bool
<= :: ConnKey -> ConnKey -> Bool
$c> :: ConnKey -> ConnKey -> Bool
> :: ConnKey -> ConnKey -> Bool
$c>= :: ConnKey -> ConnKey -> Bool
>= :: ConnKey -> ConnKey -> Bool
$cmax :: ConnKey -> ConnKey -> ConnKey
max :: ConnKey -> ConnKey -> ConnKey
$cmin :: ConnKey -> ConnKey -> ConnKey
min :: ConnKey -> ConnKey -> ConnKey
Ord, T.Typeable)
data StreamFileStatus = StreamFileStatus
{ StreamFileStatus -> Int64
fileSize :: Int64
, StreamFileStatus -> Int64
readSoFar :: Int64
, StreamFileStatus -> Int
thisChunkSize :: Int
}
deriving (StreamFileStatus -> StreamFileStatus -> Bool
(StreamFileStatus -> StreamFileStatus -> Bool)
-> (StreamFileStatus -> StreamFileStatus -> Bool)
-> Eq StreamFileStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StreamFileStatus -> StreamFileStatus -> Bool
== :: StreamFileStatus -> StreamFileStatus -> Bool
$c/= :: StreamFileStatus -> StreamFileStatus -> Bool
/= :: StreamFileStatus -> StreamFileStatus -> Bool
Eq, Int -> StreamFileStatus -> ShowS
[StreamFileStatus] -> ShowS
StreamFileStatus -> String
(Int -> StreamFileStatus -> ShowS)
-> (StreamFileStatus -> String)
-> ([StreamFileStatus] -> ShowS)
-> Show StreamFileStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StreamFileStatus -> ShowS
showsPrec :: Int -> StreamFileStatus -> ShowS
$cshow :: StreamFileStatus -> String
show :: StreamFileStatus -> String
$cshowList :: [StreamFileStatus] -> ShowS
showList :: [StreamFileStatus] -> ShowS
Show, Eq StreamFileStatus
Eq StreamFileStatus =>
(StreamFileStatus -> StreamFileStatus -> Ordering)
-> (StreamFileStatus -> StreamFileStatus -> Bool)
-> (StreamFileStatus -> StreamFileStatus -> Bool)
-> (StreamFileStatus -> StreamFileStatus -> Bool)
-> (StreamFileStatus -> StreamFileStatus -> Bool)
-> (StreamFileStatus -> StreamFileStatus -> StreamFileStatus)
-> (StreamFileStatus -> StreamFileStatus -> StreamFileStatus)
-> Ord StreamFileStatus
StreamFileStatus -> StreamFileStatus -> Bool
StreamFileStatus -> StreamFileStatus -> Ordering
StreamFileStatus -> StreamFileStatus -> StreamFileStatus
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StreamFileStatus -> StreamFileStatus -> Ordering
compare :: StreamFileStatus -> StreamFileStatus -> Ordering
$c< :: StreamFileStatus -> StreamFileStatus -> Bool
< :: StreamFileStatus -> StreamFileStatus -> Bool
$c<= :: StreamFileStatus -> StreamFileStatus -> Bool
<= :: StreamFileStatus -> StreamFileStatus -> Bool
$c> :: StreamFileStatus -> StreamFileStatus -> Bool
> :: StreamFileStatus -> StreamFileStatus -> Bool
$c>= :: StreamFileStatus -> StreamFileStatus -> Bool
>= :: StreamFileStatus -> StreamFileStatus -> Bool
$cmax :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
max :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
$cmin :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
min :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
Ord, T.Typeable)