PageRenderTime 652ms CodeModel.GetById 20ms RepoModel.GetById 0ms app.codeStats 0ms

/Network/Wreq.hs

https://gitlab.com/tunixman/wreq
Haskell | 623 lines | 189 code | 50 blank | 384 comment | 0 complexity | 64ac78e42f48229a3dfe16ebaf87327a MD5 | raw file
  1. {-# LANGUAGE FlexibleContexts, OverloadedStrings #-}
  2. -- |
  3. -- Module : Network.Wreq
  4. -- Copyright : (c) 2014 Bryan O'Sullivan
  5. --
  6. -- License : BSD-style
  7. -- Maintainer : bos@serpentine.com
  8. -- Stability : experimental
  9. -- Portability : GHC
  10. --
  11. -- A library for client-side HTTP requests, focused on ease of use.
  12. --
  13. -- When reading the examples in this module, you should assume the
  14. -- following environment:
  15. --
  16. -- @
  17. -- \-\- Make it easy to write literal 'S.ByteString' and 'Text' values.
  18. -- \{\-\# LANGUAGE OverloadedStrings \#\-\}
  19. --
  20. -- \-\- Our handy module.
  21. -- import "Network.Wreq"
  22. --
  23. -- \-\- Operators such as ('&') and ('.~').
  24. -- import "Control.Lens"
  25. --
  26. -- \-\- Conversion of Haskell values to JSON.
  27. -- import "Data.Aeson" ('Data.Aeson.toJSON')
  28. --
  29. -- \-\- Easy traversal of JSON data.
  30. -- import "Data.Aeson.Lens" ('Data.Aeson.Lens.key', 'Data.Aeson.Lens.nth')
  31. -- @
  32. --
  33. -- There exist some less frequently used lenses that are not exported
  34. -- from this module; these can be found in "Network.Wreq.Lens".
  35. module Network.Wreq
  36. (
  37. -- * HTTP verbs
  38. -- ** Sessions
  39. -- $session
  40. -- ** GET
  41. get
  42. , getWith
  43. -- ** POST
  44. -- $postable
  45. , post
  46. , postWith
  47. -- ** HEAD
  48. , head_
  49. , headWith
  50. -- ** OPTIONS
  51. , options
  52. , optionsWith
  53. -- ** PUT
  54. , put
  55. , putWith
  56. -- ** DELETE
  57. , delete
  58. , deleteWith
  59. -- ** Custom Method
  60. , customMethod
  61. , customMethodWith
  62. -- ** Custom Payload Method
  63. , customPayloadMethod
  64. , customPayloadMethodWith
  65. -- * Incremental consumption of responses
  66. -- ** GET
  67. , foldGet
  68. , foldGetWith
  69. -- * Configuration
  70. , Options
  71. , defaults
  72. , Lens.manager
  73. , Lens.header
  74. , Lens.param
  75. , Lens.redirects
  76. , Lens.headers
  77. , Lens.params
  78. , Lens.cookie
  79. , Lens.cookies
  80. , Lens.checkStatus
  81. -- ** Authentication
  82. -- $auth
  83. , Auth
  84. , AWSAuthVersion(..)
  85. , Lens.auth
  86. , basicAuth
  87. , oauth1Auth
  88. , oauth2Bearer
  89. , oauth2Token
  90. , awsAuth
  91. -- ** Proxy settings
  92. , Proxy(Proxy)
  93. , Lens.proxy
  94. , httpProxy
  95. -- ** Using a manager with defaults
  96. , withManager
  97. -- * Payloads for POST and PUT
  98. , Payload(..)
  99. -- ** URL-encoded form data
  100. , FormParam(..)
  101. , FormValue
  102. -- ** Multipart form data
  103. , Form.Part
  104. , Lens.partName
  105. , Lens.partFileName
  106. , Lens.partContentType
  107. , Lens.partGetBody
  108. -- *** Smart constructors
  109. , Form.partBS
  110. , Form.partLBS
  111. , partText
  112. , partString
  113. , Form.partFile
  114. , Form.partFileSource
  115. -- * Responses
  116. , Response
  117. , Lens.responseBody
  118. , Lens.responseHeader
  119. , Lens.responseLink
  120. , Lens.responseCookie
  121. , Lens.responseHeaders
  122. , Lens.responseCookieJar
  123. , Lens.responseStatus
  124. , Lens.Status
  125. , Lens.statusCode
  126. , Lens.statusMessage
  127. -- ** Link headers
  128. , Lens.Link
  129. , Lens.linkURL
  130. , Lens.linkParams
  131. -- ** Decoding responses
  132. , JSONError(..)
  133. , asJSON
  134. , asValue
  135. -- * Cookies
  136. -- $cookielenses
  137. , Lens.Cookie
  138. , Lens.cookieName
  139. , Lens.cookieValue
  140. , Lens.cookieExpiryTime
  141. , Lens.cookieDomain
  142. , Lens.cookiePath
  143. -- * Parsing responses
  144. , Lens.atto
  145. , Lens.atto_
  146. ) where
  147. import Control.Lens ((.~), (&))
  148. import Control.Monad (unless)
  149. import Control.Monad.Catch (MonadThrow(throwM))
  150. import Data.Aeson (FromJSON)
  151. import Data.Maybe (fromMaybe)
  152. import Data.Text (Text)
  153. import Data.Text.Encoding (encodeUtf8)
  154. import Network.HTTP.Client.Internal (Proxy(..), Response)
  155. import Network.Wreq.Internal
  156. import Network.Wreq.Types (Options)
  157. import Network.Wreq.Types hiding (Options(..))
  158. import Prelude hiding (head)
  159. import qualified Data.Aeson as Aeson
  160. import qualified Data.ByteString as S
  161. import qualified Data.ByteString.Lazy as L
  162. import qualified Data.Text as T
  163. import qualified Network.HTTP.Client as HTTP
  164. import qualified Network.HTTP.Client.MultipartFormData as Form
  165. import qualified Network.Wreq.Lens as Lens
  166. import qualified Network.Wreq.Types as Wreq
  167. import qualified Data.ByteString.Char8 as BC8
  168. -- | Issue a GET request.
  169. --
  170. -- Example:
  171. --
  172. -- @
  173. --'get' \"http:\/\/httpbin.org\/get\"
  174. -- @
  175. --
  176. -- >>> r <- get "http://httpbin.org/get"
  177. -- >>> r ^. responseStatus . statusCode
  178. -- 200
  179. get :: String -> IO (Response L.ByteString)
  180. get url = getWith defaults url
  181. withManager :: (Options -> IO a) -> IO a
  182. withManager act = HTTP.withManager defaultManagerSettings $ \mgr ->
  183. act defaults { Wreq.manager = Right mgr }
  184. -- | Issue a GET request, using the supplied 'Options'.
  185. --
  186. -- Example:
  187. --
  188. -- @
  189. --let opts = 'defaults' '&' 'Lens.param' \"foo\" '.~' [\"bar\"]
  190. --'getWith' opts \"http:\/\/httpbin.org\/get\"
  191. -- @
  192. --
  193. -- >>> let opts = defaults & param "foo" .~ ["bar"]
  194. -- >>> r <- getWith opts "http://httpbin.org/get"
  195. -- >>> r ^? responseBody . key "url"
  196. -- Just (String "http://httpbin.org/get?foo=bar")
  197. getWith :: Options -> String -> IO (Response L.ByteString)
  198. getWith opts url = runRead =<< prepareGet opts url
  199. -- | Issue a POST request.
  200. --
  201. -- Example:
  202. --
  203. -- @
  204. --'post' \"http:\/\/httpbin.org\/post\" ('Aeson.toJSON' [1,2,3])
  205. -- @
  206. --
  207. -- >>> r <- post "http://httpbin.org/post" (toJSON [1,2,3])
  208. -- >>> r ^? responseBody . key "json" . nth 2
  209. -- Just (Number 3.0)
  210. post :: Postable a => String -> a -> IO (Response L.ByteString)
  211. post url payload = postWith defaults url payload
  212. -- | Issue a POST request, using the supplied 'Options'.
  213. --
  214. -- Example:
  215. --
  216. -- @
  217. --let opts = 'defaults' '&' 'Lens.param' \"foo\" '.~' [\"bar\"]
  218. --'postWith' opts \"http:\/\/httpbin.org\/post\" ('Aeson.toJSON' [1,2,3])
  219. -- @
  220. --
  221. -- >>> let opts = defaults & param "foo" .~ ["bar"]
  222. -- >>> r <- postWith opts "http://httpbin.org/post" (toJSON [1,2,3])
  223. -- >>> r ^? responseBody . key "url"
  224. -- Just (String "http://httpbin.org/post?foo=bar")
  225. postWith :: Postable a => Options -> String -> a -> IO (Response L.ByteString)
  226. postWith opts url payload = runRead =<< preparePost opts url payload
  227. -- | Issue a HEAD request.
  228. --
  229. -- Example:
  230. --
  231. -- @
  232. --'head_' \"http:\/\/httpbin.org\/get\"
  233. -- @
  234. --
  235. -- >>> r <- head_ "http://httpbin.org/get"
  236. -- >>> r ^? responseHeader "Content-Type"
  237. -- Just "application/json"
  238. head_ :: String -> IO (Response ())
  239. head_ = headWith (defaults & Lens.redirects .~ 0)
  240. -- | Issue a HEAD request, using the supplied 'Options'.
  241. --
  242. -- Example:
  243. --
  244. -- @
  245. --let opts = 'defaults' '&' 'Lens.param' \"foo\" '.~' [\"bar\"]
  246. --'headWith' opts \"http:\/\/httpbin.org\/get\"
  247. -- @
  248. --
  249. -- >>> let opts = defaults & param "foo" .~ ["bar"]
  250. -- >>> r <- headWith opts "http://httpbin.org/get"
  251. -- >>> r ^? responseHeader "Connection"
  252. -- Just "keep-alive"
  253. headWith :: Options -> String -> IO (Response ())
  254. headWith opts url = runIgnore =<< prepareHead opts url
  255. -- | Issue a PUT request.
  256. put :: Putable a => String -> a -> IO (Response L.ByteString)
  257. put url payload = putWith defaults url payload
  258. -- | Issue a PUT request, using the supplied 'Options'.
  259. putWith :: Putable a => Options -> String -> a -> IO (Response L.ByteString)
  260. putWith opts url payload = runRead =<< preparePut opts url payload
  261. -- | Issue an OPTIONS request.
  262. --
  263. -- Example:
  264. --
  265. -- @
  266. --'options' \"http:\/\/httpbin.org\/get\"
  267. -- @
  268. --
  269. -- See 'Lens.atto' for a more complex worked example.
  270. options :: String -> IO (Response ())
  271. options = optionsWith defaults
  272. -- | Issue an OPTIONS request, using the supplied 'Options'.
  273. --
  274. -- Example:
  275. --
  276. -- @
  277. --let opts = 'defaults' '&' 'Lens.param' \"foo\" '.~' [\"bar\"]
  278. --'optionsWith' opts \"http:\/\/httpbin.org\/get\"
  279. -- @
  280. optionsWith :: Options -> String -> IO (Response ())
  281. optionsWith opts url = runIgnore =<< prepareOptions opts url
  282. -- | Issue a DELETE request.
  283. --
  284. -- Example:
  285. --
  286. -- @
  287. --'delete' \"http:\/\/httpbin.org\/delete\"
  288. -- @
  289. --
  290. -- >>> r <- delete "http://httpbin.org/delete"
  291. -- >>> r ^. responseStatus . statusCode
  292. -- 200
  293. delete :: String -> IO (Response L.ByteString)
  294. delete = deleteWith defaults
  295. -- | Issue a DELETE request, using the supplied 'Options'.
  296. --
  297. -- Example:
  298. --
  299. -- @
  300. --let opts = 'defaults' '&' 'Lens.redirects' '.~' 0
  301. --'deleteWith' opts \"http:\/\/httpbin.org\/delete\"
  302. -- @
  303. --
  304. -- >>> let opts = defaults & redirects .~ 0
  305. -- >>> r <- deleteWith opts "http://httpbin.org/delete"
  306. -- >>> r ^. responseStatus . statusCode
  307. -- 200
  308. deleteWith :: Options -> String -> IO (Response L.ByteString)
  309. deleteWith opts url = runRead =<< prepareDelete opts url
  310. -- | Issue a custom-method request
  311. --
  312. -- Example:
  313. -- @
  314. -- 'customMethod' \"PATCH\" \"http:\/\/httpbin.org\/patch\"
  315. -- @
  316. --
  317. -- >>> r <- customMethod "PATCH" "http://httpbin.org/patch"
  318. -- >>> r ^. responseStatus . statusCode
  319. -- 200
  320. customMethod :: String -> String -> IO (Response L.ByteString)
  321. customMethod method url = customMethodWith method defaults url
  322. -- | Issue a custom request method request, using the supplied 'Options'.
  323. --
  324. -- Example:
  325. --
  326. -- @
  327. --let opts = 'defaults' '&' 'Lens.redirects' '.~' 0
  328. --'customMethodWith' \"PATCH\" opts \"http:\/\/httpbin.org\/patch\"
  329. -- @
  330. --
  331. -- >>> let opts = defaults & redirects .~ 0
  332. -- >>> r <- customMethodWith "PATCH" opts "http://httpbin.org/patch"
  333. -- >>> r ^. responseStatus . statusCode
  334. -- 200
  335. customMethodWith :: String -> Options -> String -> IO (Response L.ByteString)
  336. customMethodWith method opts url = runRead =<< prepareMethod methodBS opts url
  337. where
  338. methodBS = BC8.pack method
  339. -- | Issue a custom-method request with a payload
  340. customPayloadMethod :: Postable a => String -> String -> a
  341. -> IO (Response L.ByteString)
  342. customPayloadMethod method url payload =
  343. customPayloadMethodWith method defaults url payload
  344. -- | Issue a custom-method request with a payload, using the supplied 'Options'.
  345. customPayloadMethodWith :: Postable a => String -> Options -> String -> a
  346. -> IO (Response L.ByteString)
  347. customPayloadMethodWith method opts url payload =
  348. runRead =<< preparePayloadMethod methodBS opts url payload
  349. where
  350. methodBS = BC8.pack method
  351. foldGet :: (a -> S.ByteString -> IO a) -> a -> String -> IO a
  352. foldGet f z url = foldGetWith defaults f z url
  353. foldGetWith :: Options -> (a -> S.ByteString -> IO a) -> a -> String -> IO a
  354. foldGetWith opts f z0 url = request return opts url (foldResponseBody f z0)
  355. -- | Convert the body of an HTTP response from JSON to a suitable
  356. -- Haskell type.
  357. --
  358. -- In this example, we use 'asJSON' in the @IO@ monad, where it will
  359. -- throw a 'JSONError' exception if conversion to the desired type
  360. -- fails.
  361. --
  362. -- @
  363. -- \{-\# LANGUAGE DeriveGeneric \#-\}
  364. --import "GHC.Generics" ('GHC.Generics.Generic')
  365. --
  366. -- \{- This Haskell type corresponds to the structure of a
  367. -- response body from httpbin.org. -\}
  368. --
  369. --data GetBody = GetBody {
  370. -- headers :: 'Data.Map.Map' 'Data.Text.Text' 'Data.Text.Text'
  371. -- , args :: 'Data.Map.Map' 'Data.Text.Text' 'Data.Text.Text'
  372. -- , origin :: 'Data.Text.Text'
  373. -- , url :: 'Data.Text.Text'
  374. -- } deriving (Show, 'GHC.Generics.Generic')
  375. --
  376. -- \-\- Get GHC to derive a 'FromJSON' instance for us.
  377. --instance 'FromJSON' GetBody
  378. --
  379. -- \{- The fact that we want a GetBody below will be inferred by our
  380. -- use of the \"headers\" accessor function. -\}
  381. --
  382. --foo = do
  383. -- r <- 'asJSON' =<< 'get' \"http:\/\/httpbin.org\/get\"
  384. -- print (headers (r 'Control.Lens.^.' 'responseBody'))
  385. -- @
  386. --
  387. -- If we use 'asJSON' in the 'Either' monad, it will return 'Left'
  388. -- with a 'JSONError' payload if conversion fails, and 'Right' with a
  389. -- 'Response' whose 'responseBody' is the converted value on success.
  390. asJSON :: (MonadThrow m, FromJSON a) =>
  391. Response L.ByteString -> m (Response a)
  392. {-# SPECIALIZE asJSON :: (FromJSON a) =>
  393. Response L.ByteString -> IO (Response a) #-}
  394. {-# SPECIALIZE asJSON :: Response L.ByteString -> IO (Response Aeson.Value) #-}
  395. asJSON resp = do
  396. let contentType = fst . S.break (==59) . fromMaybe "unknown" .
  397. lookup "Content-Type" . HTTP.responseHeaders $ resp
  398. unless ("application/json" `S.isPrefixOf` contentType) $
  399. throwM . JSONError $ "content type of response is " ++ show contentType
  400. case Aeson.eitherDecode' (HTTP.responseBody resp) of
  401. Left err -> throwM (JSONError err)
  402. Right val -> return (fmap (const val) resp)
  403. -- | Convert the body of an HTTP response from JSON to a 'Value'.
  404. --
  405. -- In this example, we use 'asValue' in the @IO@ monad, where it will
  406. -- throw a 'JSONError' exception if the conversion to 'Value' fails.
  407. --
  408. -- @
  409. --foo = do
  410. -- r <- 'asValue' =<< 'get' \"http:\/\/httpbin.org\/get\"
  411. -- print (r 'Control.Lens.^?' 'responseBody' . key \"headers\" . key \"User-Agent\")
  412. -- @
  413. asValue :: (MonadThrow m) => Response L.ByteString -> m (Response Aeson.Value)
  414. {-# SPECIALIZE asValue :: Response L.ByteString
  415. -> IO (Response Aeson.Value) #-}
  416. asValue = asJSON
  417. -- $auth
  418. --
  419. -- Do not use HTTP authentication unless you are using TLS encryption.
  420. -- These authentication tokens can easily be captured and reused by an
  421. -- attacker if transmitted in the clear.
  422. -- | Basic authentication. This consists of a plain username and
  423. -- password.
  424. --
  425. -- Example (note the use of TLS):
  426. --
  427. -- @
  428. --let opts = 'defaults' '&' 'Lens.auth' '?~' 'basicAuth' \"user\" \"pass\"
  429. --'getWith' opts \"https:\/\/httpbin.org\/basic-auth\/user\/pass\"
  430. -- @
  431. --
  432. -- Note here the use of the 'Control.Lens.?~' setter to turn an 'Auth'
  433. -- into a 'Maybe' 'Auth', to make the type of the RHS compatible with
  434. -- the 'Lens.auth' lens.
  435. --
  436. -- >>> let opts = defaults & auth ?~ basicAuth "user" "pass"
  437. -- >>> r <- getWith opts "https://httpbin.org/basic-auth/user/pass"
  438. -- >>> r ^? responseBody . key "authenticated"
  439. -- Just (Bool True)
  440. basicAuth :: S.ByteString -- ^ Username.
  441. -> S.ByteString -- ^ Password.
  442. -> Auth
  443. basicAuth = BasicAuth
  444. -- | OAuth1 authentication. This consists of a consumer token,
  445. -- a consumer secret, a token and a token secret
  446. oauth1Auth :: S.ByteString -- ^ Consumer token
  447. -> S.ByteString -- ^ Consumer secret
  448. -> S.ByteString -- ^ OAuth token
  449. -> S.ByteString -- ^ OAuth token secret
  450. -> Auth
  451. oauth1Auth = OAuth1
  452. -- | An OAuth2 bearer token. This is treated by many services as the
  453. -- equivalent of a username and password.
  454. --
  455. -- Example (note the use of TLS):
  456. --
  457. -- @
  458. --let opts = 'defaults' '&' 'Lens.auth' '?~' 'oauth2Bearer' \"1234abcd\"
  459. --'getWith' opts \"https:\/\/public-api.wordpress.com\/rest\/v1\/me\/\"
  460. -- @
  461. oauth2Bearer :: S.ByteString -> Auth
  462. oauth2Bearer = OAuth2Bearer
  463. -- | A not-quite-standard OAuth2 bearer token (that seems to be used
  464. -- only by GitHub). This will be treated by whatever services accept
  465. -- it as the equivalent of a username and password.
  466. --
  467. -- Example (note the use of TLS):
  468. --
  469. -- @
  470. --let opts = 'defaults' '&' 'Lens.auth' '?~' 'oauth2Token' \"abcd1234\"
  471. --'getWith' opts \"https:\/\/api.github.com\/user\"
  472. -- @
  473. oauth2Token :: S.ByteString -> Auth
  474. oauth2Token = OAuth2Token
  475. -- | AWS v4 request signature.
  476. --
  477. -- Example (note the use of TLS):
  478. --
  479. -- @
  480. --let opts = 'defaults' '&' 'Lens.auth' '?~' 'awsAuth AWSv4' \"key\" \"secret\"
  481. --'getWith' opts \"https:\/\/dynamodb.us-west-2.amazonaws.com\"
  482. -- @
  483. awsAuth :: AWSAuthVersion -> S.ByteString -> S.ByteString -> Auth
  484. awsAuth = AWSAuth
  485. -- | Proxy configuration.
  486. --
  487. -- Example:
  488. --
  489. -- @
  490. --let opts = 'defaults' '&' 'Lens.proxy' '?~' 'httpProxy' \"localhost\" 8000
  491. --'getWith' opts \"http:\/\/httpbin.org\/get\"
  492. -- @
  493. --
  494. -- Note here the use of the 'Control.Lens.?~' setter to turn a 'Proxy'
  495. -- into a 'Maybe' 'Proxy', to make the type of the RHS compatible with
  496. -- the 'Lens.proxy' lens.
  497. httpProxy :: S.ByteString -> Int -> Proxy
  498. httpProxy = Proxy
  499. -- | Make a 'Part' whose content is a strict 'T.Text', encoded as
  500. -- UTF-8.
  501. --
  502. -- The 'Part' does not have a file name or content type associated
  503. -- with it.
  504. partText :: Text -- ^ Name of the corresponding \<input\>.
  505. -> Text -- ^ The body for this 'Form.Part'.
  506. -> Form.Part
  507. partText name value = Form.partBS name (encodeUtf8 value)
  508. -- | Make a 'Part' whose content is a 'String', encoded as UTF-8.
  509. --
  510. -- The 'Part' does not have a file name or content type associated
  511. -- with it.
  512. partString :: Text -- ^ Name of the corresponding \<input\>.
  513. -> String -- ^ The body for this 'Form.Part'.
  514. -> Form.Part
  515. partString name value = Form.partBS name (encodeUtf8 (T.pack value))
  516. -- $session
  517. --
  518. -- The basic HTTP functions ('get', 'post', and so on) in this module
  519. -- have a few key drawbacks:
  520. --
  521. -- * If several requests go to the same server, there is no reuse of
  522. -- TCP connections.
  523. --
  524. -- * There is no management of cookies across multiple requests.
  525. --
  526. -- This makes these functions inefficient and verbose for many common
  527. -- uses. For greater efficiency, use the "Network.Wreq.Session"
  528. -- module.
  529. -- $cookielenses
  530. --
  531. -- These are only the most frequently-used cookie-related lenses. See
  532. -- "Network.Wreq.Lens" for the full accounting of them all.
  533. -- $postable
  534. --
  535. -- The 'Postable' class determines which Haskell types can be used as
  536. -- POST payloads.
  537. --
  538. -- 'Form.Part' and ['Form.Part'] give a request body with a
  539. -- @Content-Type@ of @multipart/form-data@. Constructor functions
  540. -- include 'partText' and 'Form.partFile'.
  541. --
  542. -- >>> r <- post "http://httpbin.org/post" (partText "hello" "world")
  543. -- >>> r ^? responseBody . key "form" . key "hello"
  544. -- Just (String "world")
  545. --
  546. -- ('S.ByteString', 'S.ByteString') and 'FormParam' (and lists of
  547. -- each) give a request body with a @Content-Type@ of
  548. -- @application/x-www-form-urlencoded@. The easiest way to use this is
  549. -- via the (':=') constructor.
  550. --
  551. -- >>> r <- post "http://httpbin.org/post" ["num" := 31337, "str" := "foo"]
  552. -- >>> r ^? responseBody . key "form" . key "num"
  553. -- Just (String "31337")
  554. --
  555. -- The \"magical\" type conversion on the right-hand side of ':='
  556. -- above is due to the 'FormValue' class. This package provides
  557. -- sensible instances for the standard string and number types.
  558. --
  559. -- The 'Aeson.Value' type gives a JSON request body with a
  560. -- @Content-Type@ of @application/json@. Any instance of
  561. -- 'Aeson.ToJSON' can of course be converted to a 'Aeson.Value' using
  562. -- 'Aeson.toJSON'.
  563. --
  564. -- >>> r <- post "http://httpbin.org/post" (toJSON [1,2,3])
  565. -- >>> r ^? responseBody . key "json" . nth 0
  566. -- Just (Number 1.0)
  567. -- $setup
  568. --
  569. -- >>> :set -XOverloadedStrings
  570. -- >>> import Control.Lens
  571. -- >>> import Data.Aeson (toJSON)
  572. -- >>> import Data.Aeson.Lens (key, nth)
  573. -- >>> import Network.Wreq