{-# 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 (..)
, MaxHeaderLength (..)
) 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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatusHeaders] -> ShowS
$cshowList :: [StatusHeaders] -> ShowS
show :: StatusHeaders -> String
$cshow :: StatusHeaders -> String
showsPrec :: Int -> StatusHeaders -> ShowS
$cshowsPrec :: Int -> StatusHeaders -> ShowS
Show, StatusHeaders -> StatusHeaders -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatusHeaders -> StatusHeaders -> Bool
$c/= :: StatusHeaders -> StatusHeaders -> Bool
== :: StatusHeaders -> StatusHeaders -> Bool
$c== :: StatusHeaders -> StatusHeaders -> Bool
Eq, Eq 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
min :: StatusHeaders -> StatusHeaders -> StatusHeaders
$cmin :: StatusHeaders -> StatusHeaders -> StatusHeaders
max :: StatusHeaders -> StatusHeaders -> StatusHeaders
$cmax :: StatusHeaders -> StatusHeaders -> StatusHeaders
>= :: StatusHeaders -> StatusHeaders -> Bool
$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
compare :: StatusHeaders -> StatusHeaders -> Ordering
$ccompare :: StatusHeaders -> StatusHeaders -> Ordering
Ord, T.Typeable)
newtype HttpExceptionContentWrapper = HttpExceptionContentWrapper
{ HttpExceptionContentWrapper -> HttpExceptionContent
unHttpExceptionContentWrapper :: HttpExceptionContent
}
deriving (Int -> HttpExceptionContentWrapper -> ShowS
[HttpExceptionContentWrapper] -> ShowS
HttpExceptionContentWrapper -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpExceptionContentWrapper] -> ShowS
$cshowList :: [HttpExceptionContentWrapper] -> ShowS
show :: HttpExceptionContentWrapper -> String
$cshow :: HttpExceptionContentWrapper -> String
showsPrec :: Int -> HttpExceptionContentWrapper -> ShowS
$cshowsPrec :: Int -> HttpExceptionContentWrapper -> ShowS
Show, T.Typeable)
instance Exception HttpExceptionContentWrapper
throwHttp :: HttpExceptionContent -> IO a
throwHttp :: forall a. HttpExceptionContent -> IO a
throwHttp = forall e a. Exception e => e -> IO a
throwIO 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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpException] -> ShowS
$cshowList :: [HttpException] -> ShowS
show :: HttpException -> String
$cshow :: HttpException -> String
showsPrec :: Int -> HttpException -> ShowS
$cshowsPrec :: Int -> 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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpExceptionContent] -> ShowS
$cshowList :: [HttpExceptionContent] -> ShowS
show :: HttpExceptionContent -> String
$cshow :: HttpExceptionContent -> String
showsPrec :: Int -> HttpExceptionContent -> ShowS
$cshowsPrec :: Int -> 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]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Cookie]
$creadListPrec :: ReadPrec [Cookie]
readPrec :: ReadPrec Cookie
$creadPrec :: ReadPrec Cookie
readList :: ReadS [Cookie]
$creadList :: ReadS [Cookie]
readsPrec :: Int -> ReadS Cookie
$creadsPrec :: Int -> ReadS Cookie
Read, Int -> Cookie -> ShowS
[Cookie] -> ShowS
Cookie -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cookie] -> ShowS
$cshowList :: [Cookie] -> ShowS
show :: Cookie -> String
$cshow :: Cookie -> String
showsPrec :: Int -> Cookie -> ShowS
$cshowsPrec :: Int -> Cookie -> ShowS
Show, T.Typeable)
newtype CookieJar = CJ { CookieJar -> [Cookie]
expose :: [Cookie] }
deriving (ReadPrec [CookieJar]
ReadPrec CookieJar
Int -> ReadS CookieJar
ReadS [CookieJar]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CookieJar]
$creadListPrec :: ReadPrec [CookieJar]
readPrec :: ReadPrec CookieJar
$creadPrec :: ReadPrec CookieJar
readList :: ReadS [CookieJar]
$creadList :: ReadS [CookieJar]
readsPrec :: Int -> ReadS CookieJar
$creadsPrec :: Int -> ReadS CookieJar
Read, Int -> CookieJar -> ShowS
[CookieJar] -> ShowS
CookieJar -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CookieJar] -> ShowS
$cshowList :: [CookieJar] -> ShowS
show :: CookieJar -> String
$cshow :: CookieJar -> String
showsPrec :: Int -> CookieJar -> ShowS
$cshowsPrec :: Int -> CookieJar -> ShowS
Show, T.Typeable)
equalCookie :: Cookie -> Cookie -> Bool
equalCookie :: Cookie -> Cookie -> Bool
equalCookie Cookie
a Cookie
b = forall (t :: * -> *). Foldable t => t Bool -> Bool
and
[ Cookie -> ByteString
cookie_name Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_name Cookie
b
, Cookie -> ByteString
cookie_value Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_value Cookie
b
, Cookie -> UTCTime
cookie_expiry_time Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_expiry_time Cookie
b
, Cookie -> ByteString
cookie_domain Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_domain Cookie
b
, Cookie -> ByteString
cookie_path Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_path Cookie
b
, Cookie -> UTCTime
cookie_creation_time Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_creation_time Cookie
b
, Cookie -> UTCTime
cookie_last_access_time Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> UTCTime
cookie_last_access_time Cookie
b
, Cookie -> Bool
cookie_persistent Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_persistent Cookie
b
, Cookie -> Bool
cookie_host_only Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_host_only Cookie
b
, Cookie -> Bool
cookie_secure_only Cookie
a forall a. Eq a => a -> a -> Bool
== Cookie -> Bool
cookie_secure_only Cookie
b
, Cookie -> Bool
cookie_http_only Cookie
a 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 forall a. Eq a => a -> a -> Bool
== Cookie -> ByteString
cookie_name Cookie
b
domain_matches :: Bool
domain_matches = forall s. FoldCase s => s -> s
CI.foldCase (Cookie -> ByteString
cookie_domain Cookie
a) forall a. Eq a => a -> a -> Bool
== 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 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) 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) 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 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) = forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall a b. (a -> b) -> a -> b
$ 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 = forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Cookie -> Cookie -> Bool
equivCookie (forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
compareCookies forall a b. (a -> b) -> a -> b
$ CookieJar -> [Cookie]
expose CookieJar
cj1) (forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
compareCookies 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 (forall a. (a -> a -> Bool) -> [a] -> [a]
DL.nubBy Cookie -> Cookie -> Bool
equivCookie forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Ordering) -> [a] -> [a]
DL.sortBy Cookie -> Cookie -> Ordering
mostRecentFirst forall a b. (a -> b) -> a -> b
$ [Cookie]
a 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 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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Proxy] -> ShowS
$cshowList :: [Proxy] -> ShowS
show :: Proxy -> String
$cshow :: Proxy -> String
showsPrec :: Int -> Proxy -> ShowS
$cshowsPrec :: Int -> Proxy -> ShowS
Show, ReadPrec [Proxy]
ReadPrec Proxy
Int -> ReadS Proxy
ReadS [Proxy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Proxy]
$creadListPrec :: ReadPrec [Proxy]
readPrec :: ReadPrec Proxy
$creadPrec :: ReadPrec Proxy
readList :: ReadS [Proxy]
$creadList :: ReadS [Proxy]
readsPrec :: Int -> ReadS Proxy
$creadsPrec :: Int -> ReadS Proxy
Read, Proxy -> Proxy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Proxy -> Proxy -> Bool
$c/= :: Proxy -> Proxy -> Bool
== :: Proxy -> Proxy -> Bool
$c== :: Proxy -> Proxy -> Bool
Eq, Eq 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
min :: Proxy -> Proxy -> Proxy
$cmin :: Proxy -> Proxy -> Proxy
max :: Proxy -> Proxy -> Proxy
$cmax :: Proxy -> Proxy -> Proxy
>= :: Proxy -> Proxy -> Bool
$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
compare :: Proxy -> Proxy -> Ordering
$ccompare :: Proxy -> Proxy -> Ordering
Ord, T.Typeable)
data ProxySecureMode =
ProxySecureWithConnect
| ProxySecureWithoutConnect
deriving (Int -> ProxySecureMode -> ShowS
[ProxySecureMode] -> ShowS
ProxySecureMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxySecureMode] -> ShowS
$cshowList :: [ProxySecureMode] -> ShowS
show :: ProxySecureMode -> String
$cshow :: ProxySecureMode -> String
showsPrec :: Int -> ProxySecureMode -> ShowS
$cshowsPrec :: Int -> ProxySecureMode -> ShowS
Show, ReadPrec [ProxySecureMode]
ReadPrec ProxySecureMode
Int -> ReadS ProxySecureMode
ReadS [ProxySecureMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ProxySecureMode]
$creadListPrec :: ReadPrec [ProxySecureMode]
readPrec :: ReadPrec ProxySecureMode
$creadPrec :: ReadPrec ProxySecureMode
readList :: ReadS [ProxySecureMode]
$creadList :: ReadS [ProxySecureMode]
readsPrec :: Int -> ReadS ProxySecureMode
$creadsPrec :: Int -> ReadS ProxySecureMode
Read, ProxySecureMode -> ProxySecureMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProxySecureMode -> ProxySecureMode -> Bool
$c/= :: ProxySecureMode -> ProxySecureMode -> Bool
== :: ProxySecureMode -> ProxySecureMode -> Bool
$c== :: ProxySecureMode -> ProxySecureMode -> Bool
Eq, Eq 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
min :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
$cmin :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
max :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
$cmax :: ProxySecureMode -> ProxySecureMode -> ProxySecureMode
>= :: ProxySecureMode -> ProxySecureMode -> Bool
$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
compare :: ProxySecureMode -> ProxySecureMode -> Ordering
$ccompare :: ProxySecureMode -> ProxySecureMode -> Ordering
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 (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 forall a. Num a => a -> a -> a
+ Int64
j) (Builder
x 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 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 forall a b. (a -> b) -> a -> b
$ \IO ByteString
x' -> GivesPopper ()
y 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 <- forall a. a -> IO (IORef a)
newIORef forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (IO ByteString
x, IO ByteString
y)
NeedsPopper ()
f 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 <- 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
forall a. IORef a -> a -> IO ()
writeIORef IORef (Either (IO ByteString, IO ByteString) (IO ByteString))
istate forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right IO ByteString
y
IO ByteString
y
else 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) = forall a b. a -> Either a b
Left (ByteString -> Int64
L.length ByteString
lbs, ByteString -> Builder
fromLazyByteString ByteString
lbs)
simplify (RequestBodyBS ByteString
bs) = forall a b. a -> Either a b
Left (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
S.length ByteString
bs, ByteString -> Builder
fromByteString ByteString
bs)
simplify (RequestBodyBuilder Int64
len Builder
b) = forall a b. a -> Either a b
Left (Int64
len, Builder
b)
simplify (RequestBodyStream Int64
i GivesPopper ()
gp) = forall a b. b -> Either a b
Right (forall a. a -> Maybe a
Just Int64
i, GivesPopper ()
gp)
simplify (RequestBodyStreamChunked GivesPopper ()
gp) = forall a b. b -> Either a b
Right (forall a. Maybe a
Nothing, GivesPopper ()
gp)
simplify (RequestBodyIO IO RequestBody
_mbody) = 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) =
(forall a. a -> Maybe a
Just Int64
len, 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 <- forall a. a -> IO (IORef a)
newIORef forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
L.toChunks forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
toLazyByteString Builder
builder
IO ByteString -> IO b
np forall a b. (a -> b) -> a -> b
$ do
[ByteString]
bss <- forall a. IORef a -> IO a
readIORef IORef [ByteString]
ibss
case [ByteString]
bss of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
S.empty
ByteString
bs:[ByteString]
bss' -> do
forall a. IORef a -> a -> IO ()
writeIORef IORef [ByteString]
ibss [ByteString]
bss'
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseTimeout -> ResponseTimeout -> Bool
$c/= :: ResponseTimeout -> ResponseTimeout -> Bool
== :: ResponseTimeout -> ResponseTimeout -> Bool
$c== :: ResponseTimeout -> ResponseTimeout -> Bool
Eq, Int -> ResponseTimeout -> ShowS
[ResponseTimeout] -> ShowS
ResponseTimeout -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseTimeout] -> ShowS
$cshowList :: [ResponseTimeout] -> ShowS
show :: ResponseTimeout -> String
$cshow :: ResponseTimeout -> String
showsPrec :: Int -> ResponseTimeout -> ShowS
$cshowsPrec :: Int -> ResponseTimeout -> ShowS
Show)
instance Show Request where
show :: Request -> String
show Request
x = [String] -> String
unlines
[ String
"Request {"
, String
" host = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> ByteString
host Request
x)
, String
" port = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> Int
port Request
x)
, String
" secure = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> Bool
secure Request
x)
, String
" requestHeaders = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a b. (a -> b) -> [a] -> [b]
DL.map (Set HeaderName
-> (HeaderName, ByteString) -> (HeaderName, ByteString)
redactSensitiveHeader forall a b. (a -> b) -> a -> b
$ Request -> Set HeaderName
redactHeaders Request
x) (Request -> RequestHeaders
requestHeaders Request
x))
, String
" path = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> ByteString
path Request
x)
, String
" queryString = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> ByteString
queryString Request
x)
, String
" method = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> ByteString
method Request
x)
, String
" proxy = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> Maybe Proxy
proxy Request
x)
, String
" rawBody = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> Bool
rawBody Request
x)
, String
" redirectCount = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> Int
redirectCount Request
x)
, String
" responseTimeout = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> ResponseTimeout
responseTimeout Request
x)
, String
" requestVersion = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Request -> HttpVersion
requestVersion Request
x)
, String
" proxySecureMode = " forall a. [a] -> [a] -> [a]
++ 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 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
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
showList :: [Response body] -> ShowS
$cshowList :: forall body. Show body => [Response body] -> ShowS
show :: Response body -> String
$cshow :: forall body. Show body => Response body -> String
showsPrec :: Int -> Response body -> ShowS
$cshowsPrec :: forall body. Show body => Int -> Response body -> ShowS
Show, T.Typeable, 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
<$ :: forall a b. a -> Response b -> Response a
$c<$ :: forall a b. a -> Response b -> Response a
fmap :: forall a b. (a -> b) -> Response a -> Response b
$cfmap :: forall a b. (a -> b) -> Response a -> Response b
Functor, 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
product :: forall a. Num a => Response a -> a
$cproduct :: forall a. Num a => Response a -> a
sum :: forall a. Num a => Response a -> a
$csum :: forall a. Num a => Response a -> a
minimum :: forall a. Ord a => Response a -> a
$cminimum :: forall a. Ord a => Response a -> a
maximum :: forall a. Ord a => Response a -> a
$cmaximum :: forall a. Ord a => Response a -> a
elem :: forall a. Eq a => a -> Response a -> Bool
$celem :: forall a. Eq a => a -> Response a -> Bool
length :: forall a. Response a -> Int
$clength :: forall a. Response a -> Int
null :: forall a. Response a -> Bool
$cnull :: forall a. Response a -> Bool
toList :: forall a. Response a -> [a]
$ctoList :: forall a. Response a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Response a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Response a -> a
foldr1 :: forall a. (a -> a -> a) -> Response a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Response a -> a
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
$cfoldl :: forall b a. (b -> a -> 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
$cfoldr :: forall a b. (a -> b -> b) -> b -> Response a -> b
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
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Response a -> m
fold :: forall m. Monoid m => Response m -> m
$cfold :: forall m. Monoid m => Response m -> m
Data.Foldable.Foldable, Functor Response
Foldable 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)
sequence :: forall (m :: * -> *) a. Monad m => Response (m a) -> m (Response a)
$csequence :: forall (m :: * -> *) a. Monad m => Response (m a) -> m (Response a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Response a -> m (Response b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Response (f a) -> f (Response a)
traverse :: 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)
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
, :: Maybe MaxHeaderLength
}
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)
, :: Maybe MaxHeaderLength
}
deriving T.Typeable
class HasHttpManager a where
getHttpManager :: a -> Manager
instance HasHttpManager Manager where
getHttpManager :: Manager -> Manager
getHttpManager = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnHost -> ConnHost -> Bool
$c/= :: ConnHost -> ConnHost -> Bool
== :: ConnHost -> ConnHost -> Bool
$c== :: ConnHost -> ConnHost -> Bool
Eq, Int -> ConnHost -> ShowS
[ConnHost] -> ShowS
ConnHost -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnHost] -> ShowS
$cshowList :: [ConnHost] -> ShowS
show :: ConnHost -> String
$cshow :: ConnHost -> String
showsPrec :: Int -> ConnHost -> ShowS
$cshowsPrec :: Int -> ConnHost -> ShowS
Show, Eq 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
min :: ConnHost -> ConnHost -> ConnHost
$cmin :: ConnHost -> ConnHost -> ConnHost
max :: ConnHost -> ConnHost -> ConnHost
$cmax :: ConnHost -> ConnHost -> ConnHost
>= :: ConnHost -> ConnHost -> Bool
$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
compare :: ConnHost -> ConnHost -> Ordering
$ccompare :: ConnHost -> ConnHost -> Ordering
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnKey -> ConnKey -> Bool
$c/= :: ConnKey -> ConnKey -> Bool
== :: ConnKey -> ConnKey -> Bool
$c== :: ConnKey -> ConnKey -> Bool
Eq, Int -> ConnKey -> ShowS
[ConnKey] -> ShowS
ConnKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnKey] -> ShowS
$cshowList :: [ConnKey] -> ShowS
show :: ConnKey -> String
$cshow :: ConnKey -> String
showsPrec :: Int -> ConnKey -> ShowS
$cshowsPrec :: Int -> ConnKey -> ShowS
Show, Eq 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
min :: ConnKey -> ConnKey -> ConnKey
$cmin :: ConnKey -> ConnKey -> ConnKey
max :: ConnKey -> ConnKey -> ConnKey
$cmax :: ConnKey -> ConnKey -> ConnKey
>= :: ConnKey -> ConnKey -> Bool
$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
compare :: ConnKey -> ConnKey -> Ordering
$ccompare :: ConnKey -> ConnKey -> Ordering
Ord, T.Typeable)
data StreamFileStatus = StreamFileStatus
{ StreamFileStatus -> Int64
fileSize :: Int64
, StreamFileStatus -> Int64
readSoFar :: Int64
, StreamFileStatus -> Int
thisChunkSize :: Int
}
deriving (StreamFileStatus -> StreamFileStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamFileStatus -> StreamFileStatus -> Bool
$c/= :: StreamFileStatus -> StreamFileStatus -> Bool
== :: StreamFileStatus -> StreamFileStatus -> Bool
$c== :: StreamFileStatus -> StreamFileStatus -> Bool
Eq, Int -> StreamFileStatus -> ShowS
[StreamFileStatus] -> ShowS
StreamFileStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StreamFileStatus] -> ShowS
$cshowList :: [StreamFileStatus] -> ShowS
show :: StreamFileStatus -> String
$cshow :: StreamFileStatus -> String
showsPrec :: Int -> StreamFileStatus -> ShowS
$cshowsPrec :: Int -> StreamFileStatus -> ShowS
Show, Eq 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
min :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
$cmin :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
max :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
$cmax :: StreamFileStatus -> StreamFileStatus -> StreamFileStatus
>= :: StreamFileStatus -> StreamFileStatus -> Bool
$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
compare :: StreamFileStatus -> StreamFileStatus -> Ordering
$ccompare :: StreamFileStatus -> StreamFileStatus -> Ordering
Ord, T.Typeable)
newtype =
{ :: Int
}
deriving (MaxHeaderLength -> MaxHeaderLength -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaxHeaderLength -> MaxHeaderLength -> Bool
$c/= :: MaxHeaderLength -> MaxHeaderLength -> Bool
== :: MaxHeaderLength -> MaxHeaderLength -> Bool
$c== :: MaxHeaderLength -> MaxHeaderLength -> Bool
Eq, Int -> MaxHeaderLength -> ShowS
[MaxHeaderLength] -> ShowS
MaxHeaderLength -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaxHeaderLength] -> ShowS
$cshowList :: [MaxHeaderLength] -> ShowS
show :: MaxHeaderLength -> String
$cshow :: MaxHeaderLength -> String
showsPrec :: Int -> MaxHeaderLength -> ShowS
$cshowsPrec :: Int -> MaxHeaderLength -> ShowS
Show)