{-# LANGUAGE FlexibleContexts, OverloadedStrings #-}
module Network.Wreq
(
get
, getWith
, post
, postWith
, head_
, headWith
, options
, optionsWith
, put
, putWith
, delete
, deleteWith
, customMethod
, customMethodWith
, customHistoriedMethod
, customHistoriedMethodWith
, customPayloadMethod
, customPayloadMethodWith
, customHistoriedPayloadMethod
, customHistoriedPayloadMethodWith
, foldGet
, foldGetWith
, Options
, defaults
, Lens.manager
, Lens.header
, Lens.param
, Lens.redirects
, Lens.headers
, Lens.params
, Lens.cookie
, Lens.cookies
, Lens.checkResponse
, Auth
, AWSAuthVersion(..)
, Lens.auth
, basicAuth
, oauth1Auth
, oauth2Bearer
, oauth2Token
, awsAuth
, awsFullAuth
, awsSessionTokenAuth
, Proxy(Proxy)
, Lens.proxy
, httpProxy
, withManager
, Payload(..)
, FormParam(..)
, FormValue
, Form.Part
, Lens.partName
, Lens.partFileName
, Lens.partContentType
, Lens.partGetBody
, Form.partBS
, Form.partLBS
, partText
, partString
, Form.partFile
, Form.partFileSource
, Response
, Lens.responseBody
, Lens.responseHeader
, Lens.responseLink
, Lens.responseCookie
, Lens.responseHeaders
, Lens.responseCookieJar
, Lens.responseStatus
, Lens.Status
, Lens.statusCode
, Lens.statusMessage
, HistoriedResponse
, Lens.hrFinalRequest
, Lens.hrFinalResponse
, Lens.hrRedirects
, Lens.Link
, Lens.linkURL
, Lens.linkParams
, JSONError(..)
, asJSON
, asValue
, Lens.Cookie
, Lens.cookieName
, Lens.cookieValue
, Lens.cookieExpiryTime
, Lens.cookieDomain
, Lens.cookiePath
, Lens.atto
, Lens.atto_
) where
import Control.Lens ((.~), (&))
import Control.Monad (unless)
import Control.Monad.Catch (MonadThrow(throwM))
import Data.Aeson (FromJSON)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Text.Encoding (encodeUtf8)
import Network.HTTP.Client (HistoriedResponse)
import Network.HTTP.Client.Internal (Proxy(..), Response)
import Network.Wreq.Internal
import Network.Wreq.Types (Options)
import Network.Wreq.Types hiding (Options(..))
import Prelude hiding (head)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.MultipartFormData as Form
import qualified Network.Wreq.Lens as Lens
import qualified Network.Wreq.Types as Wreq
import qualified Data.ByteString.Char8 as BC8
get :: String -> IO (Response L.ByteString)
get :: String -> IO (Response ByteString)
get String
url = Options -> String -> IO (Response ByteString)
getWith Options
defaults String
url
withManager :: (Options -> IO a) -> IO a
withManager :: (Options -> IO a) -> IO a
withManager Options -> IO a
act = do
Manager
mgr <- ManagerSettings -> IO Manager
HTTP.newManager ManagerSettings
defaultManagerSettings
Options -> IO a
act Options
defaults { manager :: Mgr
Wreq.manager = Manager -> Mgr
forall a b. b -> Either a b
Right Manager
mgr }
getWith :: Options -> String -> IO (Response L.ByteString)
getWith :: Options -> String -> IO (Response ByteString)
getWith Options
opts String
url = Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> IO Req
prepareGet Options
opts String
url
post :: Postable a => String -> a -> IO (Response L.ByteString)
post :: String -> a -> IO (Response ByteString)
post String
url a
payload = Options -> String -> a -> IO (Response ByteString)
forall a.
Postable a =>
Options -> String -> a -> IO (Response ByteString)
postWith Options
defaults String
url a
payload
postWith :: Postable a => Options -> String -> a -> IO (Response L.ByteString)
postWith :: Options -> String -> a -> IO (Response ByteString)
postWith Options
opts String
url a
payload = Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> a -> IO Req
forall a. Postable a => Options -> String -> a -> IO Req
preparePost Options
opts String
url a
payload
head_ :: String -> IO (Response ())
head_ :: String -> IO (Response ())
head_ = Options -> String -> IO (Response ())
headWith (Options
defaults Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& (Int -> Identity Int) -> Options -> Identity Options
Lens' Options Int
Lens.redirects ((Int -> Identity Int) -> Options -> Identity Options)
-> Int -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
0)
headWith :: Options -> String -> IO (Response ())
headWith :: Options -> String -> IO (Response ())
headWith Options
opts String
url = Run ()
runIgnore Run () -> IO Req -> IO (Response ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> IO Req
prepareHead Options
opts String
url
put :: Putable a => String -> a -> IO (Response L.ByteString)
put :: String -> a -> IO (Response ByteString)
put String
url a
payload = Options -> String -> a -> IO (Response ByteString)
forall a.
Putable a =>
Options -> String -> a -> IO (Response ByteString)
putWith Options
defaults String
url a
payload
putWith :: Putable a => Options -> String -> a -> IO (Response L.ByteString)
putWith :: Options -> String -> a -> IO (Response ByteString)
putWith Options
opts String
url a
payload = Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> a -> IO Req
forall a. Putable a => Options -> String -> a -> IO Req
preparePut Options
opts String
url a
payload
options :: String -> IO (Response ())
options :: String -> IO (Response ())
options = Options -> String -> IO (Response ())
optionsWith Options
defaults
optionsWith :: Options -> String -> IO (Response ())
optionsWith :: Options -> String -> IO (Response ())
optionsWith Options
opts String
url = Run ()
runIgnore Run () -> IO Req -> IO (Response ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> IO Req
prepareOptions Options
opts String
url
delete :: String -> IO (Response L.ByteString)
delete :: String -> IO (Response ByteString)
delete = Options -> String -> IO (Response ByteString)
deleteWith Options
defaults
deleteWith :: Options -> String -> IO (Response L.ByteString)
deleteWith :: Options -> String -> IO (Response ByteString)
deleteWith Options
opts String
url = Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> String -> IO Req
prepareDelete Options
opts String
url
customMethod :: String -> String -> IO (Response L.ByteString)
customMethod :: String -> String -> IO (Response ByteString)
customMethod String
method String
url = String -> Options -> String -> IO (Response ByteString)
customMethodWith String
method Options
defaults String
url
customMethodWith :: String -> Options -> String -> IO (Response L.ByteString)
customMethodWith :: String -> Options -> String -> IO (Response ByteString)
customMethodWith String
method Options
opts String
url = Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Method -> Options -> String -> IO Req
prepareMethod Method
methodBS Options
opts String
url
where
methodBS :: Method
methodBS = String -> Method
BC8.pack String
method
customHistoriedMethod :: String -> String -> IO (HistoriedResponse L.ByteString)
customHistoriedMethod :: String -> String -> IO (HistoriedResponse ByteString)
customHistoriedMethod String
method String
url = String -> Options -> String -> IO (HistoriedResponse ByteString)
customHistoriedMethodWith String
method Options
defaults String
url
customHistoriedMethodWith :: String -> Options -> String -> IO (HistoriedResponse L.ByteString)
customHistoriedMethodWith :: String -> Options -> String -> IO (HistoriedResponse ByteString)
customHistoriedMethodWith String
method Options
opts String
url =
RunHistory ByteString
runReadHistory RunHistory ByteString
-> IO Req -> IO (HistoriedResponse ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Method -> Options -> String -> IO Req
prepareMethod Method
methodBS Options
opts String
url
where
methodBS :: Method
methodBS = String -> Method
BC8.pack String
method
customPayloadMethod :: Postable a => String -> String -> a
-> IO (Response L.ByteString)
customPayloadMethod :: String -> String -> a -> IO (Response ByteString)
customPayloadMethod String
method String
url a
payload =
String -> Options -> String -> a -> IO (Response ByteString)
forall a.
Postable a =>
String -> Options -> String -> a -> IO (Response ByteString)
customPayloadMethodWith String
method Options
defaults String
url a
payload
customPayloadMethodWith :: Postable a => String -> Options -> String -> a
-> IO (Response L.ByteString)
customPayloadMethodWith :: String -> Options -> String -> a -> IO (Response ByteString)
customPayloadMethodWith String
method Options
opts String
url a
payload =
Run ByteString
runRead Run ByteString -> IO Req -> IO (Response ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Method -> Options -> String -> a -> IO Req
forall a. Postable a => Method -> Options -> String -> a -> IO Req
preparePayloadMethod Method
methodBS Options
opts String
url a
payload
where
methodBS :: Method
methodBS = String -> Method
BC8.pack String
method
customHistoriedPayloadMethod :: Postable a => String -> String -> a
-> IO (HistoriedResponse L.ByteString)
customHistoriedPayloadMethod :: String -> String -> a -> IO (HistoriedResponse ByteString)
customHistoriedPayloadMethod String
method String
url a
payload =
String
-> Options -> String -> a -> IO (HistoriedResponse ByteString)
forall a.
Postable a =>
String
-> Options -> String -> a -> IO (HistoriedResponse ByteString)
customHistoriedPayloadMethodWith String
method Options
defaults String
url a
payload
customHistoriedPayloadMethodWith :: Postable a => String -> Options -> String -> a
-> IO (HistoriedResponse L.ByteString)
customHistoriedPayloadMethodWith :: String
-> Options -> String -> a -> IO (HistoriedResponse ByteString)
customHistoriedPayloadMethodWith String
method Options
opts String
url a
payload =
RunHistory ByteString
runReadHistory RunHistory ByteString
-> IO Req -> IO (HistoriedResponse ByteString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Method -> Options -> String -> a -> IO Req
forall a. Postable a => Method -> Options -> String -> a -> IO Req
preparePayloadMethod Method
methodBS Options
opts String
url a
payload
where
methodBS :: Method
methodBS = String -> Method
BC8.pack String
method
foldGet :: (a -> S.ByteString -> IO a) -> a -> String -> IO a
foldGet :: (a -> Method -> IO a) -> a -> String -> IO a
foldGet a -> Method -> IO a
f a
z String
url = Options -> (a -> Method -> IO a) -> a -> String -> IO a
forall a. Options -> (a -> Method -> IO a) -> a -> String -> IO a
foldGetWith Options
defaults a -> Method -> IO a
f a
z String
url
foldGetWith :: Options -> (a -> S.ByteString -> IO a) -> a -> String -> IO a
foldGetWith :: Options -> (a -> Method -> IO a) -> a -> String -> IO a
foldGetWith Options
opts a -> Method -> IO a
f a
z0 String
url = (Request -> IO Request)
-> Options -> String -> (Response BodyReader -> IO a) -> IO a
forall a.
(Request -> IO Request)
-> Options -> String -> (Response BodyReader -> IO a) -> IO a
request Request -> IO Request
forall (m :: * -> *) a. Monad m => a -> m a
return Options
opts String
url ((a -> Method -> IO a) -> a -> Response BodyReader -> IO a
forall a. (a -> Method -> IO a) -> a -> Response BodyReader -> IO a
foldResponseBody a -> Method -> IO a
f a
z0)
asJSON :: (MonadThrow m, FromJSON a) =>
Response L.ByteString -> m (Response a)
{-# SPECIALIZE asJSON :: (FromJSON a) =>
Response L.ByteString -> IO (Response a) #-}
{-# SPECIALIZE asJSON :: Response L.ByteString -> IO (Response Aeson.Value) #-}
asJSON :: Response ByteString -> m (Response a)
asJSON Response ByteString
resp = do
let contentType :: Method
contentType = (Method, Method) -> Method
forall a b. (a, b) -> a
fst ((Method, Method) -> Method)
-> (Response ByteString -> (Method, Method))
-> Response ByteString
-> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool) -> Method -> (Method, Method)
S.break (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
59) (Method -> (Method, Method))
-> (Response ByteString -> Method)
-> Response ByteString
-> (Method, Method)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Maybe Method -> Method
forall a. a -> Maybe a -> a
fromMaybe Method
"unknown" (Maybe Method -> Method)
-> (Response ByteString -> Maybe Method)
-> Response ByteString
-> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
HeaderName -> [(HeaderName, Method)] -> Maybe Method
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"Content-Type" ([(HeaderName, Method)] -> Maybe Method)
-> (Response ByteString -> [(HeaderName, Method)])
-> Response ByteString
-> Maybe Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response ByteString -> [(HeaderName, Method)]
forall body. Response body -> [(HeaderName, Method)]
HTTP.responseHeaders (Response ByteString -> Method) -> Response ByteString -> Method
forall a b. (a -> b) -> a -> b
$ Response ByteString
resp
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Method
"application/json" Method -> Method -> Bool
`S.isPrefixOf` Method
contentType
Bool -> Bool -> Bool
|| (Method
"application/" Method -> Method -> Bool
`S.isPrefixOf` Method
contentType Bool -> Bool -> Bool
&& Method
"+json" Method -> Method -> Bool
`S.isSuffixOf` Method
contentType)) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
JSONError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (JSONError -> m ()) -> (String -> JSONError) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> JSONError
JSONError (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"content type of response is " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Method -> String
forall a. Show a => a -> String
show Method
contentType
case ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecode' (Response ByteString -> ByteString
forall body. Response body -> body
HTTP.responseBody Response ByteString
resp) of
Left String
err -> JSONError -> m (Response a)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (String -> JSONError
JSONError String
err)
Right a
val -> Response a -> m (Response a)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteString -> a) -> Response ByteString -> Response a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> ByteString -> a
forall a b. a -> b -> a
const a
val) Response ByteString
resp)
asValue :: (MonadThrow m) => Response L.ByteString -> m (Response Aeson.Value)
{-# SPECIALIZE asValue :: Response L.ByteString
-> IO (Response Aeson.Value) #-}
asValue :: Response ByteString -> m (Response Value)
asValue = Response ByteString -> m (Response Value)
forall (m :: * -> *) a.
(MonadThrow m, FromJSON a) =>
Response ByteString -> m (Response a)
asJSON
basicAuth :: S.ByteString
-> S.ByteString
-> Auth
basicAuth :: Method -> Method -> Auth
basicAuth = Method -> Method -> Auth
BasicAuth
oauth1Auth :: S.ByteString
-> S.ByteString
-> S.ByteString
-> S.ByteString
-> Auth
oauth1Auth :: Method -> Method -> Method -> Method -> Auth
oauth1Auth = Method -> Method -> Method -> Method -> Auth
OAuth1
oauth2Bearer :: S.ByteString -> Auth
oauth2Bearer :: Method -> Auth
oauth2Bearer = Method -> Auth
OAuth2Bearer
oauth2Token :: S.ByteString -> Auth
oauth2Token :: Method -> Auth
oauth2Token = Method -> Auth
OAuth2Token
awsAuth :: AWSAuthVersion -> S.ByteString -> S.ByteString -> Auth
awsAuth :: AWSAuthVersion -> Method -> Method -> Auth
awsAuth AWSAuthVersion
version Method
key Method
secret = AWSAuthVersion -> Method -> Method -> Maybe Method -> Auth
AWSAuth AWSAuthVersion
version Method
key Method
secret Maybe Method
forall a. Maybe a
Nothing
awsSessionTokenAuth :: AWSAuthVersion
-> S.ByteString
-> S.ByteString
-> S.ByteString
-> Auth
awsSessionTokenAuth :: AWSAuthVersion -> Method -> Method -> Method -> Auth
awsSessionTokenAuth AWSAuthVersion
version Method
key Method
secret Method
sessionToken =
AWSAuthVersion -> Method -> Method -> Maybe Method -> Auth
AWSAuth AWSAuthVersion
version Method
key Method
secret (Method -> Maybe Method
forall a. a -> Maybe a
Just Method
sessionToken)
awsFullAuth :: AWSAuthVersion -> S.ByteString -> S.ByteString -> Maybe S.ByteString -> Maybe (S.ByteString, S.ByteString) -> Auth
awsFullAuth :: AWSAuthVersion
-> Method
-> Method
-> Maybe Method
-> Maybe (Method, Method)
-> Auth
awsFullAuth = AWSAuthVersion
-> Method
-> Method
-> Maybe Method
-> Maybe (Method, Method)
-> Auth
AWSFullAuth
httpProxy :: S.ByteString -> Int -> Proxy
httpProxy :: Method -> Int -> Proxy
httpProxy = Method -> Int -> Proxy
Proxy
partText :: Text
-> Text
-> Form.Part
partText :: Text -> Text -> Part
partText Text
name Text
value = Text -> Method -> Part
forall (m :: * -> *). Applicative m => Text -> Method -> PartM m
Form.partBS Text
name (Text -> Method
encodeUtf8 Text
value)
partString :: Text
-> String
-> Form.Part
partString :: Text -> String -> Part
partString Text
name String
value = Text -> Method -> Part
forall (m :: * -> *). Applicative m => Text -> Method -> PartM m
Form.partBS Text
name (Text -> Method
encodeUtf8 (String -> Text
T.pack String
value))