File: Client.hs

package info (click to toggle)
haskell-http-client 0.7.17-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 528 kB
  • sloc: haskell: 4,029; makefile: 3
file content (404 lines) | stat: -rw-r--r-- 13,892 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE CPP #-}
-- |
--
-- = Simpler API
--
-- The API below is rather low-level. The @Network.HTTP.Simple@ module (from
-- the @http-conduit@ package) provides a higher-level API with built-in
-- support for things like JSON request and response bodies. For most users,
-- this will be an easier place to start. You can read the tutorial at:
--
-- https://github.com/snoyberg/http-client/blob/master/TUTORIAL.md
--
-- = Lower-level API
--
-- This is the main entry point for using http-client. Used by itself, this
-- module provides low-level access for streaming request and response bodies,
-- and only non-secure HTTP connections. Helper packages such as http-conduit
-- provide higher level streaming approaches, while other helper packages like
-- http-client-tls provide secure connections.
--
-- There are three core components to be understood here: requests, responses,
-- and managers. A 'Manager' keeps track of open connections to various hosts,
-- and when requested, will provide either an existing open connection or
-- create a new connection on demand. A 'Manager' also automatically reaps
-- connections which have been unused for a certain period of time. A 'Manager'
-- allows for more efficient HTTP usage by allowing for keep-alive connections.
-- Secure HTTP connections can be allowed by modifying the settings used for
-- creating a manager. The simplest way to create a 'Manager' is with:
--
-- @
-- 'newManager' 'defaultManagerSettings'
-- @
--
-- While generally speaking it is a good idea to share a single 'Manager'
-- throughout your application, there are cases where it makes more sense to
-- create and destroy 'Manager's more frequently. As an example, if you have an
-- application which will make a large number of requests to different hosts,
-- and will never make more than one connection to a single host, then sharing
-- a 'Manager' will result in idle connections being kept open longer than
-- necessary. In such a situation, it makes sense to use 'newManager' before
-- each new request, to avoid running out of file descriptors. (Note that the
-- 'managerIdleConnectionCount' setting mitigates the risk of leaking too many
-- file descriptors.)
--
-- The next core component is a 'Request', which represents a single HTTP
-- request to be sent to a specific server. 'Request's allow for many settings
-- to control exact how they function, but usually the simplest approach for
-- creating a 'Request' is to use 'parseRequest'.
--
-- Finally, a 'Response' is the result of sending a single 'Request' to a
-- server, over a connection which was acquired from a 'Manager'. Note that you
-- must close the response when you're done with it to ensure that the
-- connection is recycled to the 'Manager' to either be used by another
-- request, or to be reaped. Usage of 'withResponse' will ensure that this
-- happens automatically.
--
-- Helper packages may provide replacements for various recommendations listed
-- above. For example, if using http-client-tls, instead of using
-- 'defaultManagerSettings', you would want to use 'tlsManagerSettings'. Be
-- sure to read the relevant helper library documentation for more information.
--
-- A note on exceptions: for the most part, all actions that perform I/O should
-- be assumed to throw an 'HttpException' in the event of some problem, and all
-- pure functions will be total. For example, 'withResponse', 'httpLbs', and
-- 'BodyReader' can all throw exceptions. Functions like 'responseStatus' and
-- 'applyBasicAuth' are guaranteed to be total (or there's a bug in the
-- library).
--
-- One thing to be cautioned about: the type of 'parseRequest' allows it to work in
-- different monads. If used in the 'IO' monad, it will throw an exception in
-- the case of an invalid URI. In addition, if you leverage the @IsString@
-- instance of the 'Request' value via @OverloadedStrings@, an invalid URI will
-- result in a partial value. Caveat emptor!
module Network.HTTP.Client
    ( -- $example1

      -- * Performing requests
      withResponse
    , httpLbs
    , httpNoBody
    , responseOpen
    , responseClose
      -- ** Tracking redirect history
    , withResponseHistory
    , responseOpenHistory
    , HistoriedResponse
    , hrRedirects
    , hrFinalRequest
    , hrFinalResponse
      -- * Connection manager
    , Manager
    , newManager
    , closeManager
    , withManager
    , HasHttpManager(..)
      -- ** Connection manager settings
    , ManagerSettings
    , defaultManagerSettings
    , managerConnCount
    , managerRawConnection
    , managerTlsConnection
    , managerResponseTimeout
    , managerRetryableException
    , managerWrapException
    , managerIdleConnectionCount
    , managerModifyRequest
    , managerModifyResponse
      -- *** Manager proxy settings
    , managerSetProxy
    , managerSetInsecureProxy
    , managerSetSecureProxy
    , managerSetMaxHeaderLength
    , ProxyOverride
    , proxyFromRequest
    , noProxy
    , useProxy
    , useProxySecureWithoutConnect
    , proxyEnvironment
    , proxyEnvironmentNamed
    , defaultProxy
      -- *** Response timeouts
    , ResponseTimeout
    , responseTimeoutMicro
    , responseTimeoutNone
    , responseTimeoutDefault
      -- *** Helpers
    , rawConnectionModifySocket
    , rawConnectionModifySocketSize
      -- * Request
      -- $parsing-request
    , parseUrl
    , parseUrlThrow
    , parseRequest
    , parseRequest_
    , requestFromURI
    , requestFromURI_
    , defaultRequest
    , applyBasicAuth
    , applyBearerAuth
    , urlEncodedBody
    , getUri
    , setRequestIgnoreStatus
    , setRequestCheckStatus
    , setQueryString
#if MIN_VERSION_http_types(0,12,1)
    , setQueryStringPartialEscape
#endif
      -- ** Request type and fields
    , Request
    , method
    , secure
    , host
    , port
    , path
    , queryString
    , requestHeaders
    , requestBody
    , proxy
    , applyBasicProxyAuth
    , decompress
    , redirectCount
    , shouldStripHeaderOnRedirect
    , shouldStripHeaderOnRedirectIfOnDifferentHostOnly
    , checkResponse
    , responseTimeout
    , cookieJar
    , requestVersion
    , redactHeaders
    , earlyHintHeadersReceived
      -- ** Request body
    , RequestBody (..)
    , Popper
    , NeedsPopper
    , GivesPopper
    , streamFile
    , observedStreamFile
    , StreamFileStatus (..)
      -- * Response
    , Response
    , responseStatus
    , responseVersion
    , responseHeaders
    , responseBody
    , responseCookieJar
    , getOriginalRequest
    , responseEarlyHints
    , throwErrorStatusCodes
      -- ** Response body
    , BodyReader
    , brRead
    , brReadSome
    , brConsume
      -- * Advanced connection creation
    , makeConnection
    , socketConnection
      -- * Misc
    , HttpException (..)
    , HttpExceptionContent (..)
    , Cookie (..)
    , equalCookie
    , equivCookie
    , compareCookies
    , CookieJar
    , equalCookieJar
    , equivCookieJar
    , Proxy (..)
    , withConnection
    , strippedHostName
      -- * Cookies
    , module Network.HTTP.Client.Cookies
    ) where

import Network.HTTP.Client.Body
import Network.HTTP.Client.Connection (makeConnection, socketConnection, strippedHostName)
import Network.HTTP.Client.Cookies
import Network.HTTP.Client.Core
import Network.HTTP.Client.Manager
import Network.HTTP.Client.Request
import Network.HTTP.Client.Response
import Network.HTTP.Client.Types

import Data.IORef (newIORef, writeIORef, readIORef, modifyIORef)
import qualified Data.ByteString.Lazy as L
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
import Network.HTTP.Types (statusCode)
import GHC.Generics (Generic)
import Data.Typeable (Typeable)
import Control.Exception (bracket, catch, handle, throwIO)

-- | A datatype holding information on redirected requests and the final response.
--
-- Since 0.4.1
data HistoriedResponse body = HistoriedResponse
    { hrRedirects :: [(Request, Response L.ByteString)]
    -- ^ Requests which resulted in a redirect, together with their responses.
    -- The response contains the first 1024 bytes of the body.
    --
    -- Since 0.4.1
    , hrFinalRequest :: Request
    -- ^ The final request performed.
    --
    -- Since 0.4.1
    , hrFinalResponse :: Response body
    -- ^ The response from the final request.
    --
    -- Since 0.4.1
    }
    deriving (Functor, Data.Traversable.Traversable, Data.Foldable.Foldable, Show, Typeable, Generic)

-- | A variant of @responseOpen@ which keeps a history of all redirects
-- performed in the interim, together with the first 1024 bytes of their
-- response bodies.
--
-- Since 0.4.1
responseOpenHistory :: Request -> Manager -> IO (HistoriedResponse BodyReader)
responseOpenHistory reqOrig man0 = handle (throwIO . toHttpException reqOrig) $ do
    reqRef <- newIORef reqOrig
    historyRef <- newIORef id
    let go req0 = do
            (man, req) <- getModifiedRequestManager man0 req0
            (req', res') <- httpRaw' req man
            let res = res'
                    { responseBody = handle (throwIO . toHttpException req0)
                                            (responseBody res')
                    }
            case getRedirectedRequest
                    req
                    req'
                    (responseHeaders res)
                    (responseCookieJar res)
                    (statusCode $ responseStatus res) of
                Nothing -> return (res, req', False)
                Just req'' -> do
                    writeIORef reqRef req''
                    body <- brReadSome (responseBody res) 1024
                        `catch` handleClosedRead
                    modifyIORef historyRef (. ((req, res { responseBody = body }):))
                    return (res, req'', True)
    (_, res) <- httpRedirect' (redirectCount reqOrig) go reqOrig
    reqFinal <- readIORef reqRef
    history <- readIORef historyRef
    return HistoriedResponse
        { hrRedirects = history []
        , hrFinalRequest = reqFinal
        , hrFinalResponse = res
        }

-- | A variant of @withResponse@ which keeps a history of all redirects
-- performed in the interim, together with the first 1024 bytes of their
-- response bodies.
--
-- Since 0.4.1
withResponseHistory :: Request
                    -> Manager
                    -> (HistoriedResponse BodyReader -> IO a)
                    -> IO a
withResponseHistory req man = bracket
    (responseOpenHistory req man)
    (responseClose . hrFinalResponse)

-- | Set the proxy override value, only for HTTP (insecure) connections.
--
-- Since 0.4.7
managerSetInsecureProxy :: ProxyOverride -> ManagerSettings -> ManagerSettings
managerSetInsecureProxy po m = m { managerProxyInsecure = po }

-- | Set the proxy override value, only for HTTPS (secure) connections.
--
-- Since 0.4.7
managerSetSecureProxy :: ProxyOverride -> ManagerSettings -> ManagerSettings
managerSetSecureProxy po m = m { managerProxySecure = po }

-- | Set the proxy override value, for both HTTP (insecure) and HTTPS
-- (insecure) connections.
--
-- Since 0.4.7
managerSetProxy :: ProxyOverride -> ManagerSettings -> ManagerSettings
managerSetProxy po = managerSetInsecureProxy po . managerSetSecureProxy po

-- @since 0.7.17
managerSetMaxHeaderLength :: Int -> ManagerSettings -> ManagerSettings
managerSetMaxHeaderLength l manager = manager
    { managerMaxHeaderLength = Just $ MaxHeaderLength l }

-- $example1
-- = Example Usage
--
-- === Making a GET request
--
-- > import Network.HTTP.Client
-- > import Network.HTTP.Types.Status (statusCode)
-- >
-- > main :: IO ()
-- > main = do
-- >   manager <- newManager defaultManagerSettings
-- >
-- >   request <- parseRequest "http://httpbin.org/get"
-- >   response <- httpLbs request manager
-- >
-- >   putStrLn $ "The status code was: " ++ (show $ statusCode $ responseStatus response)
-- >   print $ responseBody response
--
--
-- === Posting JSON to a server
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- > import Network.HTTP.Client
-- > import Network.HTTP.Types.Status (statusCode)
-- > import Data.Aeson (object, (.=), encode)
-- > import Data.Text (Text)
-- >
-- > main :: IO ()
-- > main = do
-- >   manager <- newManager defaultManagerSettings
-- >
-- >   -- Create the request
-- >   let requestObject = object ["name" .= "Michael", "age" .= 30]
-- >   let requestObject = object
-- >        [ "name" .= ("Michael" :: Text)
-- >        , "age"  .= (30 :: Int)
-- >        ]
-- >
-- >   initialRequest <- parseRequest "http://httpbin.org/post"
-- >   let request = initialRequest { method = "POST", requestBody = RequestBodyLBS $ encode requestObject }
-- >
-- >   response <- httpLbs request manager
-- >   putStrLn $ "The status code was: " ++ (show $ statusCode $ responseStatus response)
-- >   print $ responseBody response
--

-- | Specify maximum time in microseconds the retrieval of response
-- headers is allowed to take
--
-- @since 0.5.0
responseTimeoutMicro :: Int -> ResponseTimeout
responseTimeoutMicro = ResponseTimeoutMicro

-- | Do not have a response timeout
--
-- @since 0.5.0
responseTimeoutNone :: ResponseTimeout
responseTimeoutNone = ResponseTimeoutNone

-- | Use the default response timeout
--
-- When used on a 'Request', means: use the manager's timeout value
--
-- When used on a 'ManagerSettings', means: default to 30 seconds
--
-- @since 0.5.0
responseTimeoutDefault :: ResponseTimeout
responseTimeoutDefault = ResponseTimeoutDefault

-- $parsing-request
--
-- The way you parse string of characters to construct a 'Request' will
-- determine whether exceptions will be thrown on non-2XX response status
-- codes. This is because the behavior is controlled by a setting in
-- 'Request' itself (see 'checkResponse') and different parsing functions
-- set it to different 'IO' actions.