1{-# LANGUAGE CPP #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE DeriveTraversable #-}
4{-# LANGUAGE RankNTypes #-}
5{-# LANGUAGE OverloadedStrings #-}
6module Network.HTTP.Client.Types
7    ( BodyReader
8    , Connection (..)
9    , StatusHeaders (..)
10    , HttpException (..)
11    , HttpExceptionContent (..)
12    , unHttpExceptionContentWrapper
13    , throwHttp
14    , toHttpException
15    , Cookie (..)
16    , equalCookie
17    , equivCookie
18    , compareCookies
19    , CookieJar (..)
20    , equalCookieJar
21    , equivCookieJar
22    , Proxy (..)
23    , RequestBody (..)
24    , Popper
25    , NeedsPopper
26    , GivesPopper
27    , Request (..)
28    , Response (..)
29    , ResponseClose (..)
30    , Manager (..)
31    , HasHttpManager (..)
32    , ConnsMap (..)
33    , ManagerSettings (..)
34    , NonEmptyList (..)
35    , ConnHost (..)
36    , ConnKey (..)
37    , ProxyOverride (..)
38    , StreamFileStatus (..)
39    , ResponseTimeout (..)
40    , ProxySecureMode (..)
41    ) where
42
43import qualified Data.Typeable as T (Typeable)
44import Network.HTTP.Types
45import Control.Exception (Exception, SomeException, throwIO)
46import Data.Word (Word64)
47import qualified Data.ByteString as S
48import qualified Data.ByteString.Lazy as L
49import Blaze.ByteString.Builder (Builder, fromLazyByteString, fromByteString, toLazyByteString)
50import Data.Int (Int64)
51import Data.Foldable (Foldable)
52import Data.Monoid (Monoid(..))
53import Data.Semigroup (Semigroup(..))
54import Data.String (IsString, fromString)
55import Data.Time (UTCTime)
56import Data.Traversable (Traversable)
57import qualified Data.List as DL
58import Network.Socket (HostAddress)
59import Data.IORef
60import qualified Network.Socket as NS
61import qualified Data.Map as Map
62import Data.Text (Text)
63import Data.Streaming.Zlib (ZlibException)
64import Data.CaseInsensitive as CI
65import Data.KeyedPool (KeyedPool)
66
67-- | An @IO@ action that represents an incoming response body coming from the
68-- server. Data provided by this action has already been gunzipped and
69-- de-chunked, and respects any content-length headers present.
70--
71-- The action gets a single chunk of data from the response body, or an empty
72-- bytestring if no more data is available.
73--
74-- Since 0.4.0
75type BodyReader = IO S.ByteString
76
77data Connection = Connection
78    { connectionRead :: IO S.ByteString
79      -- ^ If no more data, return empty.
80    , connectionUnread :: S.ByteString -> IO ()
81      -- ^ Return data to be read next time.
82    , connectionWrite :: S.ByteString -> IO ()
83      -- ^ Send data to server
84    , connectionClose :: IO ()
85      -- ^ Close connection. Any successive operation on the connection
86      -- (except closing) should fail with `ConnectionClosed` exception.
87      -- It is allowed to close connection multiple times.
88    }
89    deriving T.Typeable
90
91data StatusHeaders = StatusHeaders Status HttpVersion RequestHeaders
92    deriving (Show, Eq, Ord, T.Typeable)
93
94-- | A newtype wrapper which is not exported from this library but is an
95-- instance of @Exception@. This allows @HttpExceptionContent@ to be thrown
96-- (via this wrapper), but users of the library can't accidentally try to catch
97-- it (when they /should/ be trying to catch 'HttpException').
98--
99-- @since 0.5.0
100newtype HttpExceptionContentWrapper = HttpExceptionContentWrapper
101    { unHttpExceptionContentWrapper :: HttpExceptionContent
102    }
103    deriving (Show, T.Typeable)
104instance Exception HttpExceptionContentWrapper
105
106throwHttp :: HttpExceptionContent -> IO a
107throwHttp = throwIO . HttpExceptionContentWrapper
108
109toHttpException :: Request -> HttpExceptionContentWrapper -> HttpException
110toHttpException req (HttpExceptionContentWrapper e) = HttpExceptionRequest req e
111
112-- | An exception which may be generated by this library
113--
114-- @since 0.5.0
115data HttpException
116    = HttpExceptionRequest Request HttpExceptionContent
117    -- ^ Most exceptions are specific to a 'Request'. Inspect the
118    -- 'HttpExceptionContent' value for details on what occurred.
119    --
120    -- @since 0.5.0
121    | InvalidUrlException String String
122    -- ^ A URL (first field) is invalid for a given reason
123    -- (second argument).
124    --
125    -- @since 0.5.0
126    deriving (Show, T.Typeable)
127instance Exception HttpException
128
129data HttpExceptionContent
130                   = StatusCodeException (Response ()) S.ByteString
131                   -- ^ Generated by the @parseUrlThrow@ function when the
132                   -- server returns a non-2XX response status code.
133                   --
134                   -- May include the beginning of the response body.
135                   --
136                   -- @since 0.5.0
137                   | TooManyRedirects [Response L.ByteString]
138                   -- ^ The server responded with too many redirects for a
139                   -- request.
140                   --
141                   -- Contains the list of encountered responses containing
142                   -- redirects in reverse chronological order; including last
143                   -- redirect, which triggered the exception and was not
144                   -- followed.
145                   --
146                   -- @since 0.5.0
147                   | OverlongHeaders
148                   -- ^ Either too many headers, or too many total bytes in a
149                   -- single header, were returned by the server, and the
150                   -- memory exhaustion protection in this library has kicked
151                   -- in.
152                   --
153                   -- @since 0.5.0
154                   | ResponseTimeout
155                   -- ^ The server took too long to return a response. This can
156                   -- be altered via 'responseTimeout' or
157                   -- 'managerResponseTimeout'.
158                   --
159                   -- @since 0.5.0
160                   | ConnectionTimeout
161                   -- ^ Attempting to connect to the server timed out.
162                   --
163                   -- @since 0.5.0
164                   | ConnectionFailure SomeException
165                   -- ^ An exception occurred when trying to connect to the
166                   -- server.
167                   --
168                   -- @since 0.5.0
169                   | InvalidStatusLine S.ByteString
170                   -- ^ The status line returned by the server could not be parsed.
171                   --
172                   -- @since 0.5.0
173                   | InvalidHeader S.ByteString
174                   -- ^ The given response header line could not be parsed
175                   --
176                   -- @since 0.5.0
177                   | InvalidRequestHeader S.ByteString
178                   -- ^ The given request header is not compliant (e.g. has newlines)
179                   --
180                   -- @since 0.5.14
181                   | InternalException SomeException
182                   -- ^ An exception was raised by an underlying library when
183                   -- performing the request. Most often, this is caused by a
184                   -- failing socket action or a TLS exception.
185                   --
186                   -- @since 0.5.0
187                   | ProxyConnectException S.ByteString Int Status
188                   -- ^ A non-200 status code was returned when trying to
189                   -- connect to the proxy server on the given host and port.
190                   --
191                   -- @since 0.5.0
192                   | NoResponseDataReceived
193                   -- ^ No response data was received from the server at all.
194                   -- This exception may deserve special handling within the
195                   -- library, since it may indicate that a pipelining has been
196                   -- used, and a connection thought to be open was in fact
197                   -- closed.
198                   --
199                   -- @since 0.5.0
200                   | TlsNotSupported
201                   -- ^ Exception thrown when using a @Manager@ which does not
202                   -- have support for secure connections. Typically, you will
203                   -- want to use @tlsManagerSettings@ from @http-client-tls@
204                   -- to overcome this.
205                   --
206                   -- @since 0.5.0
207                   | WrongRequestBodyStreamSize Word64 Word64
208                   -- ^ The request body provided did not match the expected size.
209                   --
210                   -- Provides the expected and actual size.
211                   --
212                   -- @since 0.4.31
213                   | ResponseBodyTooShort Word64 Word64
214                   -- ^ The returned response body is too short. Provides the
215                   -- expected size and actual size.
216                   --
217                   -- @since 0.5.0
218                   | InvalidChunkHeaders
219                   -- ^ A chunked response body had invalid headers.
220                   --
221                   -- @since 0.5.0
222                   | IncompleteHeaders
223                   -- ^ An incomplete set of response headers were returned.
224                   --
225                   -- @since 0.5.0
226                   | InvalidDestinationHost S.ByteString
227                   -- ^ The host we tried to connect to is invalid (e.g., an
228                   -- empty string).
229                   | HttpZlibException ZlibException
230                   -- ^ An exception was thrown when inflating a response body.
231                   --
232                   -- @since 0.5.0
233                   | InvalidProxyEnvironmentVariable Text Text
234                   -- ^ Values in the proxy environment variable were invalid.
235                   -- Provides the environment variable name and its value.
236                   --
237                   -- @since 0.5.0
238                   | ConnectionClosed
239                   -- ^ Attempted to use a 'Connection' which was already closed
240                   --
241                   -- @since 0.5.0
242                   | InvalidProxySettings Text
243                   -- ^ Proxy settings are not valid (Windows specific currently)
244                   -- @since 0.5.7
245    deriving (Show, T.Typeable)
246
247-- Purposely not providing this instance, since we don't want users to
248-- accidentally try and catch these exceptions instead of HttpException
249--
250-- instance Exception HttpExceptionContent
251
252
253-- This corresponds to the description of a cookie detailed in Section 5.3 \"Storage Model\"
254data Cookie = Cookie
255  { cookie_name :: S.ByteString
256  , cookie_value :: S.ByteString
257  , cookie_expiry_time :: UTCTime
258  , cookie_domain :: S.ByteString
259  , cookie_path :: S.ByteString
260  , cookie_creation_time :: UTCTime
261  , cookie_last_access_time :: UTCTime
262  , cookie_persistent :: Bool
263  , cookie_host_only :: Bool
264  , cookie_secure_only :: Bool
265  , cookie_http_only :: Bool
266  }
267  deriving (Read, Show, T.Typeable)
268
269newtype CookieJar = CJ { expose :: [Cookie] }
270  deriving (Read, Show, T.Typeable)
271
272-- | Instead of '(==)'.
273--
274-- Since there was some confusion in the history of this library about how the 'Eq' instance
275-- should work, it was removed for clarity, and replaced by 'equal' and 'equiv'.  'equal'
276-- gives you equality of all fields of the 'Cookie' record.
277--
278-- @since 0.7.0
279equalCookie :: Cookie -> Cookie -> Bool
280equalCookie a b = and
281  [ cookie_name a == cookie_name b
282  , cookie_value a == cookie_value b
283  , cookie_expiry_time a == cookie_expiry_time b
284  , cookie_domain a == cookie_domain b
285  , cookie_path a == cookie_path b
286  , cookie_creation_time a == cookie_creation_time b
287  , cookie_last_access_time a == cookie_last_access_time b
288  , cookie_persistent a == cookie_persistent b
289  , cookie_host_only a == cookie_host_only b
290  , cookie_secure_only a == cookie_secure_only b
291  , cookie_http_only a == cookie_http_only b
292  ]
293
294-- | Equality of name, domain, path only.  This corresponds to step 11 of the algorithm
295-- described in Section 5.3 \"Storage Model\".  See also: 'equal'.
296--
297-- @since 0.7.0
298equivCookie :: Cookie -> Cookie -> Bool
299equivCookie a b = name_matches && domain_matches && path_matches
300  where name_matches = cookie_name a == cookie_name b
301        domain_matches = CI.foldCase (cookie_domain a) == CI.foldCase (cookie_domain b)
302        path_matches = cookie_path a == cookie_path b
303
304-- | Instead of @instance Ord Cookie@.  See 'equalCookie', 'equivCookie'.
305--
306-- @since 0.7.0
307compareCookies :: Cookie -> Cookie -> Ordering
308compareCookies c1 c2
309    | S.length (cookie_path c1) > S.length (cookie_path c2) = LT
310    | S.length (cookie_path c1) < S.length (cookie_path c2) = GT
311    | cookie_creation_time c1 > cookie_creation_time c2 = GT
312    | otherwise = LT
313
314-- | See 'equalCookie'.
315--
316-- @since 0.7.0
317equalCookieJar :: CookieJar -> CookieJar -> Bool
318equalCookieJar (CJ cj1) (CJ cj2) = and $ zipWith equalCookie cj1 cj2
319
320-- | See 'equalCookieJar', 'equalCookie'.
321--
322-- @since 0.7.0
323equivCookieJar :: CookieJar -> CookieJar -> Bool
324equivCookieJar cj1 cj2 = and $
325  zipWith equivCookie (DL.sortBy compareCookies $ expose cj1) (DL.sortBy compareCookies $ expose cj2)
326
327instance Semigroup CookieJar where
328  (CJ a) <> (CJ b) = CJ (DL.nubBy equivCookie $ DL.sortBy mostRecentFirst $ a <> b)
329    where mostRecentFirst c1 c2 =
330            -- inverse so that recent cookies are kept by nub over older
331            if cookie_creation_time c1 > cookie_creation_time c2
332                then LT
333                else GT
334
335-- | Since 1.9
336instance Data.Monoid.Monoid CookieJar where
337  mempty = CJ []
338#if !(MIN_VERSION_base(4,11,0))
339  mappend = (<>)
340#endif
341
342-- | Define a HTTP proxy, consisting of a hostname and port number.
343
344data Proxy = Proxy
345    { proxyHost :: S.ByteString -- ^ The host name of the HTTP proxy.
346    , proxyPort :: Int -- ^ The port number of the HTTP proxy.
347    }
348    deriving (Show, Read, Eq, Ord, T.Typeable)
349
350-- | Define how to make secure connections using a proxy server.
351data ProxySecureMode =
352  ProxySecureWithConnect
353  -- ^ Use the HTTP CONNECT verb to forward a secure connection through the proxy.
354  | ProxySecureWithoutConnect
355  -- ^ Send the request directly to the proxy with an https URL. This mode can be
356  -- used to offload TLS handling to a trusted local proxy.
357  deriving (Show, Read, Eq, Ord, T.Typeable)
358
359-- | When using one of the 'RequestBodyStream' \/ 'RequestBodyStreamChunked'
360-- constructors, you must ensure that the 'GivesPopper' can be called multiple
361-- times.  Usually this is not a problem.
362--
363-- The 'RequestBodyStreamChunked' will send a chunked request body. Note that
364-- not all servers support this. Only use 'RequestBodyStreamChunked' if you
365-- know the server you're sending to supports chunked request bodies.
366--
367-- Since 0.1.0
368data RequestBody
369    = RequestBodyLBS L.ByteString
370    | RequestBodyBS S.ByteString
371    | RequestBodyBuilder Int64 Builder
372    | RequestBodyStream Int64 (GivesPopper ())
373    | RequestBodyStreamChunked (GivesPopper ())
374    | RequestBodyIO (IO RequestBody)
375    -- ^ Allows creation of a @RequestBody@ inside the @IO@ monad, which is
376    -- useful for making easier APIs (like @setRequestBodyFile@).
377    --
378    -- @since 0.4.28
379    deriving T.Typeable
380-- |
381--
382-- Since 0.4.12
383instance IsString RequestBody where
384    fromString str = RequestBodyBS (fromString str)
385instance Monoid RequestBody where
386    mempty = RequestBodyBS S.empty
387#if !(MIN_VERSION_base(4,11,0))
388    mappend = (<>)
389#endif
390
391instance Semigroup RequestBody where
392    x0 <> y0 =
393        case (simplify x0, simplify y0) of
394            (Left (i, x), Left (j, y)) -> RequestBodyBuilder (i + j) (x <> y)
395            (Left x, Right y) -> combine (builderToStream x) y
396            (Right x, Left y) -> combine x (builderToStream y)
397            (Right x, Right y) -> combine x y
398      where
399        combine (Just i, x) (Just j, y) = RequestBodyStream (i + j) (combine' x y)
400        combine (_, x) (_, y) = RequestBodyStreamChunked (combine' x y)
401
402        combine' :: GivesPopper () -> GivesPopper () -> GivesPopper ()
403        combine' x y f = x $ \x' -> y $ \y' -> combine'' x' y' f
404
405        combine'' :: Popper -> Popper -> NeedsPopper () -> IO ()
406        combine'' x y f = do
407            istate <- newIORef $ Left (x, y)
408            f $ go istate
409
410        go istate = do
411            state <- readIORef istate
412            case state of
413                Left (x, y) -> do
414                    bs <- x
415                    if S.null bs
416                        then do
417                            writeIORef istate $ Right y
418                            y
419                        else return bs
420                Right y -> y
421
422simplify :: RequestBody -> Either (Int64, Builder) (Maybe Int64, GivesPopper ())
423simplify (RequestBodyLBS lbs) = Left (L.length lbs, fromLazyByteString lbs)
424simplify (RequestBodyBS bs) = Left (fromIntegral $ S.length bs, fromByteString bs)
425simplify (RequestBodyBuilder len b) = Left (len, b)
426simplify (RequestBodyStream i gp) = Right (Just i, gp)
427simplify (RequestBodyStreamChunked gp) = Right (Nothing, gp)
428simplify (RequestBodyIO _mbody) = error "FIXME No support for Monoid on RequestBodyIO"
429
430builderToStream :: (Int64, Builder) -> (Maybe Int64, GivesPopper ())
431builderToStream (len, builder) =
432    (Just len, gp)
433  where
434    gp np = do
435        ibss <- newIORef $ L.toChunks $ toLazyByteString builder
436        np $ do
437            bss <- readIORef ibss
438            case bss of
439                [] -> return S.empty
440                bs:bss' -> do
441                    writeIORef ibss bss'
442                    return bs
443
444-- | A function which generates successive chunks of a request body, provider a
445-- single empty bytestring when no more data is available.
446--
447-- Since 0.1.0
448type Popper = IO S.ByteString
449
450-- | A function which must be provided with a 'Popper'.
451--
452-- Since 0.1.0
453type NeedsPopper a = Popper -> IO a
454
455-- | A function which will provide a 'Popper' to a 'NeedsPopper'. This
456-- seemingly convoluted structure allows for creation of request bodies which
457-- allocate scarce resources in an exception safe manner.
458--
459-- Since 0.1.0
460type GivesPopper a = NeedsPopper a -> IO a
461
462-- | All information on how to connect to a host and what should be sent in the
463-- HTTP request.
464--
465-- If you simply wish to download from a URL, see 'parseRequest'.
466--
467-- The constructor for this data type is not exposed. Instead, you should use
468-- either the 'defaultRequest' value, or 'parseRequest' to
469-- construct from a URL, and then use the records below to make modifications.
470-- This approach allows http-client to add configuration options without
471-- breaking backwards compatibility.
472--
473-- For example, to construct a POST request, you could do something like:
474--
475-- > initReq <- parseRequest "http://www.example.com/path"
476-- > let req = initReq
477-- >             { method = "POST"
478-- >             }
479--
480-- For more information, please see
481-- <http://www.yesodweb.com/book/settings-types>.
482--
483-- Since 0.1.0
484data Request = Request
485    { method :: Method
486    -- ^ HTTP request method, eg GET, POST.
487    --
488    -- Since 0.1.0
489    , secure :: Bool
490    -- ^ Whether to use HTTPS (ie, SSL).
491    --
492    -- Since 0.1.0
493    , host :: S.ByteString
494    -- ^ Requested host name, used for both the IP address to connect to and
495    -- the @host@ request header.
496    --
497    -- Since 0.1.0
498    , port :: Int
499    -- ^ The port to connect to. Also used for generating the @host@ request header.
500    --
501    -- Since 0.1.0
502    , path :: S.ByteString
503    -- ^ Everything from the host to the query string.
504    --
505    -- Since 0.1.0
506    , queryString :: S.ByteString
507    -- ^ Query string appended to the path.
508    --
509    -- Since 0.1.0
510    , requestHeaders :: RequestHeaders
511    -- ^ Custom HTTP request headers
512    --
513    -- The Content-Length and Transfer-Encoding headers are set automatically
514    -- by this module, and shall not be added to @requestHeaders@.
515    --
516    -- If not provided by the user, @Host@ will automatically be set based on
517    -- the @host@ and @port@ fields.
518    --
519    -- Moreover, the Accept-Encoding header is set implicitly to gzip for
520    -- convenience by default. This behaviour can be overridden if needed, by
521    -- setting the header explicitly to a different value. In order to omit the
522    -- Accept-Header altogether, set it to the empty string \"\". If you need an
523    -- empty Accept-Header (i.e. requesting the identity encoding), set it to a
524    -- non-empty white-space string, e.g. \" \". See RFC 2616 section 14.3 for
525    -- details about the semantics of the Accept-Header field. If you request a
526    -- content-encoding not supported by this module, you will have to decode
527    -- it yourself (see also the 'decompress' field).
528    --
529    -- Note: Multiple header fields with the same field-name will result in
530    -- multiple header fields being sent and therefore it\'s the responsibility
531    -- of the client code to ensure that the rules from RFC 2616 section 4.2
532    -- are honoured.
533    --
534    -- Since 0.1.0
535    , requestBody :: RequestBody
536    -- ^ Request body to be sent to the server.
537    --
538    -- Since 0.1.0
539    , proxy :: Maybe Proxy
540    -- ^ Optional HTTP proxy.
541    --
542    -- Since 0.1.0
543    , hostAddress :: Maybe HostAddress
544    -- ^ Optional resolved host address. May not be used by all backends.
545    --
546    -- Since 0.1.0
547    , rawBody :: Bool
548    -- ^ If @True@, a chunked and\/or gzipped body will not be
549    -- decoded. Use with caution.
550    --
551    -- Since 0.1.0
552    , decompress :: S.ByteString -> Bool
553    -- ^ Predicate to specify whether gzipped data should be
554    -- decompressed on the fly (see 'alwaysDecompress' and
555    -- 'browserDecompress'). Argument is the mime type.
556    -- Default: browserDecompress.
557    --
558    -- Since 0.1.0
559    , redirectCount :: Int
560    -- ^ How many redirects to follow when getting a resource. 0 means follow
561    -- no redirects. Default value: 10.
562    --
563    -- Since 0.1.0
564    , checkResponse :: Request -> Response BodyReader -> IO ()
565    -- ^ Check the response immediately after receiving the status and headers.
566    -- This can be useful for throwing exceptions on non-success status codes.
567    --
568    -- In previous versions of http-client, this went under the name
569    -- @checkStatus@, but was renamed to avoid confusion about the new default
570    -- behavior (doing nothing).
571    --
572    -- @since 0.5.0
573    , responseTimeout :: ResponseTimeout
574    -- ^ Number of microseconds to wait for a response (see 'ResponseTimeout'
575    -- for more information). Default: use 'managerResponseTimeout' (which by
576    -- default is 30 seconds).
577    --
578    -- Since 0.1.0
579    , cookieJar :: Maybe CookieJar
580    -- ^ A user-defined cookie jar.
581    -- If 'Nothing', no cookie handling will take place, \"Cookie\" headers
582    -- in 'requestHeaders' will be sent raw, and 'responseCookieJar' will be
583    -- empty.
584    --
585    -- Since 0.1.0
586
587    , requestVersion :: HttpVersion
588    -- ^ HTTP version to send to server.
589    --
590    -- Default: HTTP 1.1
591    --
592    -- Since 0.4.3
593
594    , onRequestBodyException :: SomeException -> IO ()
595    -- ^ How to deal with exceptions thrown while sending the request.
596    --
597    -- Default: ignore @IOException@s, rethrow all other exceptions.
598    --
599    -- Since: 0.4.6
600
601    , requestManagerOverride :: Maybe Manager
602    -- ^ A 'Manager' value that should override whatever @Manager@ value was
603    -- passed in to the HTTP request function manually. This is useful when
604    -- dealing with implicit global managers, such as in @Network.HTTP.Simple@
605    --
606    -- @since 0.4.28
607
608    , shouldStripHeaderOnRedirect :: HeaderName -> Bool
609    -- ^ Decide whether a header must be stripped from the request
610    -- when following a redirect. Default: keep all headers intact.
611    --
612    -- @since 0.6.2
613
614    , proxySecureMode :: ProxySecureMode
615    -- ^ How to proxy an HTTPS request.
616    --
617    -- Default: Use HTTP CONNECT.
618    --
619    -- @since 0.7.2
620    }
621    deriving T.Typeable
622
623-- | How to deal with timing out on retrieval of response headers.
624--
625-- @since 0.5.0
626data ResponseTimeout
627    = ResponseTimeoutMicro !Int
628    -- ^ Wait the given number of microseconds for response headers to
629    -- load, then throw an exception
630    | ResponseTimeoutNone
631    -- ^ Wait indefinitely
632    | ResponseTimeoutDefault
633    -- ^ Fall back to the manager setting ('managerResponseTimeout') or, in its
634    -- absence, Wait 30 seconds and then throw an exception.
635    deriving (Eq, Show)
636
637instance Show Request where
638    show x = unlines
639        [ "Request {"
640        , "  host                 = " ++ show (host x)
641        , "  port                 = " ++ show (port x)
642        , "  secure               = " ++ show (secure x)
643        , "  requestHeaders       = " ++ show (DL.map redactSensitiveHeader (requestHeaders x))
644        , "  path                 = " ++ show (path x)
645        , "  queryString          = " ++ show (queryString x)
646        --, "  requestBody          = " ++ show (requestBody x)
647        , "  method               = " ++ show (method x)
648        , "  proxy                = " ++ show (proxy x)
649        , "  rawBody              = " ++ show (rawBody x)
650        , "  redirectCount        = " ++ show (redirectCount x)
651        , "  responseTimeout      = " ++ show (responseTimeout x)
652        , "  requestVersion       = " ++ show (requestVersion x)
653        , "  proxySecureMode      = " ++ show (proxySecureMode x)
654        , "}"
655        ]
656
657redactSensitiveHeader :: Header -> Header
658redactSensitiveHeader ("Authorization", _) = ("Authorization", "<REDACTED>")
659redactSensitiveHeader h = h
660
661-- | A simple representation of the HTTP response.
662--
663-- Since 0.1.0
664data Response body = Response
665    { responseStatus :: Status
666    -- ^ Status code of the response.
667    --
668    -- Since 0.1.0
669    , responseVersion :: HttpVersion
670    -- ^ HTTP version used by the server.
671    --
672    -- Since 0.1.0
673    , responseHeaders :: ResponseHeaders
674    -- ^ Response headers sent by the server.
675    --
676    -- Since 0.1.0
677    , responseBody :: body
678    -- ^ Response body sent by the server.
679    --
680    -- Since 0.1.0
681    , responseCookieJar :: CookieJar
682    -- ^ Cookies set on the client after interacting with the server. If
683    -- cookies have been disabled by setting 'cookieJar' to @Nothing@, then
684    -- this will always be empty.
685    --
686    -- Since 0.1.0
687    , responseClose' :: ResponseClose
688    -- ^ Releases any resource held by this response. If the response body
689    -- has not been fully read yet, doing so after this call will likely
690    -- be impossible.
691    --
692    -- Since 0.1.0
693    , responseOriginalRequest :: Request
694    -- ^ Holds original @Request@ related to this @Response@ (with an empty body).
695    -- This field is intentionally not exported directly, but made availble
696    -- via @getOriginalRequest@ instead.
697    --
698    -- Since 0.7.8
699    }
700    deriving (Show, T.Typeable, Functor, Data.Foldable.Foldable, Data.Traversable.Traversable)
701
702-- Purposely not providing this instance.  It used to use 'equivCookieJar'
703-- semantics before 0.7.0, but should, if anything, use 'equalCookieJar'
704-- semantics.
705--
706-- instance Exception Eq
707
708newtype ResponseClose = ResponseClose { runResponseClose :: IO () }
709    deriving T.Typeable
710instance Show ResponseClose where
711    show _ = "ResponseClose"
712
713-- | Settings for a @Manager@. Please use the 'defaultManagerSettings' function and then modify
714-- individual settings. For more information, see <http://www.yesodweb.com/book/settings-types>.
715--
716-- Since 0.1.0
717data ManagerSettings = ManagerSettings
718    { managerConnCount :: Int
719      -- ^ Number of connections to a single host to keep alive. Default: 10.
720      --
721      -- Since 0.1.0
722    , managerRawConnection :: IO (Maybe NS.HostAddress -> String -> Int -> IO Connection)
723      -- ^ Create an insecure connection.
724      --
725      -- Since 0.1.0
726    , managerTlsConnection :: IO (Maybe NS.HostAddress -> String -> Int -> IO Connection)
727      -- ^ Create a TLS connection. Default behavior: throw an exception that TLS is not supported.
728      --
729      -- Since 0.1.0
730    , managerTlsProxyConnection :: IO (S.ByteString -> (Connection -> IO ()) -> String -> Maybe NS.HostAddress -> String -> Int -> IO Connection)
731      -- ^ Create a TLS proxy connection. Default behavior: throw an exception that TLS is not supported.
732      --
733      -- Since 0.2.2
734    , managerResponseTimeout :: ResponseTimeout
735      -- ^ Default timeout to be applied to requests which do not provide a
736      -- timeout value.
737      --
738      -- Default is 30 seconds
739      --
740      -- @since 0.5.0
741    , managerRetryableException :: SomeException -> Bool
742    -- ^ Exceptions for which we should retry our request if we were reusing an
743    -- already open connection. In the case of IOExceptions, for example, we
744    -- assume that the connection was closed on the server and therefore open a
745    -- new one.
746    --
747    -- Since 0.1.0
748    , managerWrapException :: forall a. Request -> IO a -> IO a
749    -- ^ Action wrapped around all attempted @Request@s, usually used to wrap
750    -- up exceptions in library-specific types.
751    --
752    -- Default: wrap all @IOException@s in the @InternalException@ constructor.
753    --
754    -- @since 0.5.0
755    , managerIdleConnectionCount :: Int
756    -- ^ Total number of idle connection to keep open at a given time.
757    --
758    -- This limit helps deal with the case where you are making a large number
759    -- of connections to different hosts. Without this limit, you could run out
760    -- of file descriptors. Additionally, it can be set to zero to prevent
761    -- reuse of any connections. Doing this is useful when the server your application
762    -- is talking to sits behind a load balancer.
763    --
764    -- Default: 512
765    --
766    -- Since 0.3.7
767    , managerModifyRequest :: Request -> IO Request
768    -- ^ Perform the given modification to a @Request@ before performing it.
769    --
770    -- This function may be called more than once during request processing.
771    -- see https://github.com/snoyberg/http-client/issues/350
772    --
773    -- Default: no modification
774    --
775    -- Since 0.4.4
776    , managerModifyResponse :: Response BodyReader -> IO (Response BodyReader)
777    -- ^ Perform the given modification to a @Response@ after receiving it.
778    --
779    -- Default: no modification
780    --
781    -- @since 0.5.5
782    , managerProxyInsecure :: ProxyOverride
783    -- ^ How HTTP proxy server settings should be discovered.
784    --
785    -- Default: respect the @proxy@ value on the @Request@ itself.
786    --
787    -- Since 0.4.7
788    , managerProxySecure :: ProxyOverride
789    -- ^ How HTTPS proxy server settings should be discovered.
790    --
791    -- Default: respect the @proxy@ value on the @Request@ itself.
792    --
793    -- Since 0.4.7
794    }
795    deriving T.Typeable
796
797-- | How the HTTP proxy server settings should be discovered.
798--
799-- Since 0.4.7
800newtype ProxyOverride = ProxyOverride
801    { runProxyOverride :: Bool -> IO (Request -> Request)
802    }
803    deriving T.Typeable
804
805-- | Keeps track of open connections for keep-alive.
806--
807-- If possible, you should share a single 'Manager' between multiple threads and requests.
808--
809-- Since 0.1.0
810data Manager = Manager
811    { mConns :: KeyedPool ConnKey Connection
812    , mResponseTimeout :: ResponseTimeout
813    -- ^ Copied from 'managerResponseTimeout'
814    , mRetryableException :: SomeException -> Bool
815    , mWrapException :: forall a. Request -> IO a -> IO a
816    , mModifyRequest :: Request -> IO Request
817    , mSetProxy :: Request -> Request
818    , mModifyResponse      :: Response BodyReader -> IO (Response BodyReader)
819    -- ^ See 'managerProxy'
820    }
821    deriving T.Typeable
822
823class HasHttpManager a where
824    getHttpManager :: a -> Manager
825instance HasHttpManager Manager where
826    getHttpManager = id
827
828data ConnsMap
829    = ManagerClosed
830    | ManagerOpen {-# UNPACK #-} !Int !(Map.Map ConnKey (NonEmptyList Connection))
831
832data NonEmptyList a =
833    One a UTCTime |
834    Cons a Int UTCTime (NonEmptyList a)
835    deriving T.Typeable
836
837-- | Hostname or resolved host address.
838data ConnHost =
839    HostName Text |
840    HostAddress NS.HostAddress
841    deriving (Eq, Show, Ord, T.Typeable)
842
843-- | @ConnKey@ consists of a hostname, a port and a @Bool@
844-- specifying whether to use SSL.
845data ConnKey
846    = CKRaw (Maybe HostAddress) {-# UNPACK #-} !S.ByteString !Int
847    | CKSecure (Maybe HostAddress) {-# UNPACK #-} !S.ByteString !Int
848    | CKProxy
849        {-# UNPACK #-} !S.ByteString
850        !Int
851
852        -- Proxy-Authorization request header
853        (Maybe S.ByteString)
854
855        -- ultimate host
856        {-# UNPACK #-} !S.ByteString
857
858        -- ultimate port
859        !Int
860    deriving (Eq, Show, Ord, T.Typeable)
861
862-- | Status of streaming a request body from a file.
863--
864-- Since 0.4.9
865data StreamFileStatus = StreamFileStatus
866    { fileSize :: Int64
867    , readSoFar :: Int64
868    , thisChunkSize :: Int
869    }
870    deriving (Eq, Show, Ord, T.Typeable)
871