{-# LANGUAGE RankNTypes #-}
module Network.Wreq.Lens
(
Options
, manager
, proxy
, auth
, header
, param
, redirects
, headers
, params
, cookie
, cookies
, ResponseChecker
, checkResponse
, Proxy
, proxyHost
, proxyPort
, Cookie
, cookieName
, cookieValue
, cookieExpiryTime
, cookieDomain
, cookiePath
, cookieCreationTime
, cookieLastAccessTime
, cookiePersistent
, cookieHostOnly
, cookieSecureOnly
, cookieHttpOnly
, Response
, responseBody
, responseHeader
, responseLink
, responseCookie
, responseHeaders
, responseCookieJar
, responseStatus
, responseVersion
, HistoriedResponse
, hrFinalResponse
, hrFinalRequest
, hrRedirects
, Status
, statusCode
, statusMessage
, Link
, linkURL
, linkParams
, Part
, partName
, partFileName
, partContentType
, partGetBody
, atto
, atto_
) where
import Control.Applicative ((<*))
import Control.Lens (Fold, Lens, Lens', Traversal', folding)
import Data.Attoparsec.ByteString (Parser, endOfInput, parseOnly)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Network.HTTP.Client (Cookie, CookieJar, Request, Manager, ManagerSettings, Proxy, HistoriedResponse)
import Network.HTTP.Client (RequestBody, Response)
import Network.HTTP.Client.MultipartFormData (Part)
import Network.HTTP.Types.Header (Header, HeaderName, ResponseHeaders)
import Network.HTTP.Types.Status (Status)
import Network.HTTP.Types.Version (HttpVersion)
import Network.Mime (MimeType)
import Network.Wreq.Types (Auth, Link, Options, ResponseChecker)
import qualified Network.Wreq.Lens.TH as TH
manager :: Lens' Options (Either ManagerSettings Manager)
manager :: Lens' Options (Either ManagerSettings Manager)
manager = (Either ManagerSettings Manager
-> f (Either ManagerSettings Manager))
-> Options -> f Options
Lens' Options (Either ManagerSettings Manager)
TH.manager
proxy :: Lens' Options (Maybe Proxy)
proxy :: Lens' Options (Maybe Proxy)
proxy = (Maybe Proxy -> f (Maybe Proxy)) -> Options -> f Options
Lens' Options (Maybe Proxy)
TH.proxy
auth :: Lens' Options (Maybe Auth)
auth :: Lens' Options (Maybe Auth)
auth = (Maybe Auth -> f (Maybe Auth)) -> Options -> f Options
Lens' Options (Maybe Auth)
TH.auth
header :: HeaderName -> Lens' Options [ByteString]
= HeaderName
-> ([ByteString] -> f [ByteString]) -> Options -> f Options
HeaderName -> Lens' Options [ByteString]
TH.header
headers :: Lens' Options [Header]
= ([Header] -> f [Header]) -> Options -> f Options
Lens' Options [Header]
TH.headers
param :: Text -> Lens' Options [Text]
param :: Text -> Lens' Options [Text]
param = Text -> ([Text] -> f [Text]) -> Options -> f Options
Text -> Lens' Options [Text]
TH.param
params :: Lens' Options [(Text, Text)]
params :: Lens' Options [(Text, Text)]
params = ([(Text, Text)] -> f [(Text, Text)]) -> Options -> f Options
Lens' Options [(Text, Text)]
TH.params
redirects :: Lens' Options Int
redirects :: Lens' Options Int
redirects = (Int -> f Int) -> Options -> f Options
Lens' Options Int
TH.redirects
checkResponse :: Lens' Options (Maybe ResponseChecker)
checkResponse :: Lens' Options (Maybe ResponseChecker)
checkResponse = (Maybe ResponseChecker -> f (Maybe ResponseChecker))
-> Options -> f Options
Lens' Options (Maybe ResponseChecker)
TH.checkResponse
cookie :: ByteString -> Traversal' Options Cookie
cookie :: ByteString -> Traversal' Options Cookie
cookie = ByteString -> (Cookie -> f Cookie) -> Options -> f Options
ByteString -> Traversal' Options Cookie
TH.cookie
cookies :: Lens' Options (Maybe CookieJar)
cookies :: Lens' Options (Maybe CookieJar)
cookies = (Maybe CookieJar -> f (Maybe CookieJar)) -> Options -> f Options
Lens' Options (Maybe CookieJar)
TH.cookies
cookieName :: Lens' Cookie ByteString
cookieName :: Lens' Cookie ByteString
cookieName = (ByteString -> f ByteString) -> Cookie -> f Cookie
Lens' Cookie ByteString
TH.cookieName
cookieValue :: Lens' Cookie ByteString
cookieValue :: Lens' Cookie ByteString
cookieValue = (ByteString -> f ByteString) -> Cookie -> f Cookie
Lens' Cookie ByteString
TH.cookieValue
cookieExpiryTime :: Lens' Cookie UTCTime
cookieExpiryTime :: Lens' Cookie UTCTime
cookieExpiryTime = (UTCTime -> f UTCTime) -> Cookie -> f Cookie
Lens' Cookie UTCTime
TH.cookieExpiryTime
cookieDomain :: Lens' Cookie ByteString
cookieDomain :: Lens' Cookie ByteString
cookieDomain = (ByteString -> f ByteString) -> Cookie -> f Cookie
Lens' Cookie ByteString
TH.cookieDomain
cookiePath :: Lens' Cookie ByteString
cookiePath :: Lens' Cookie ByteString
cookiePath = (ByteString -> f ByteString) -> Cookie -> f Cookie
Lens' Cookie ByteString
TH.cookiePath
cookieCreationTime :: Lens' Cookie UTCTime
cookieCreationTime :: Lens' Cookie UTCTime
cookieCreationTime = (UTCTime -> f UTCTime) -> Cookie -> f Cookie
Lens' Cookie UTCTime
TH.cookieCreationTime
cookieLastAccessTime :: Lens' Cookie UTCTime
cookieLastAccessTime :: Lens' Cookie UTCTime
cookieLastAccessTime = (UTCTime -> f UTCTime) -> Cookie -> f Cookie
Lens' Cookie UTCTime
TH.cookieLastAccessTime
cookiePersistent :: Lens' Cookie Bool
cookiePersistent :: Lens' Cookie Bool
cookiePersistent = (Bool -> f Bool) -> Cookie -> f Cookie
Lens' Cookie Bool
TH.cookiePersistent
cookieHostOnly :: Lens' Cookie Bool
cookieHostOnly :: Lens' Cookie Bool
cookieHostOnly = (Bool -> f Bool) -> Cookie -> f Cookie
Lens' Cookie Bool
TH.cookieHostOnly
cookieSecureOnly :: Lens' Cookie Bool
cookieSecureOnly :: Lens' Cookie Bool
cookieSecureOnly = (Bool -> f Bool) -> Cookie -> f Cookie
Lens' Cookie Bool
TH.cookieSecureOnly
cookieHttpOnly :: Lens' Cookie Bool
cookieHttpOnly :: Lens' Cookie Bool
cookieHttpOnly = (Bool -> f Bool) -> Cookie -> f Cookie
Lens' Cookie Bool
TH.cookieHttpOnly
proxyHost :: Lens' Proxy ByteString
proxyHost :: Lens' Proxy ByteString
proxyHost = (ByteString -> f ByteString) -> Proxy -> f Proxy
Lens' Proxy ByteString
TH.proxyHost
proxyPort :: Lens' Proxy Int
proxyPort :: Lens' Proxy Int
proxyPort = (Int -> f Int) -> Proxy -> f Proxy
Lens' Proxy Int
TH.proxyPort
responseStatus :: Lens' (Response body) Status
responseStatus :: forall body (f :: * -> *).
Functor f =>
(Status -> f Status) -> Response body -> f (Response body)
responseStatus = (Status -> f Status) -> Response body -> f (Response body)
forall body (f :: * -> *).
Functor f =>
(Status -> f Status) -> Response body -> f (Response body)
TH.responseStatus
responseVersion :: Lens' (Response body) HttpVersion
responseVersion :: forall body (f :: * -> *).
Functor f =>
(HttpVersion -> f HttpVersion)
-> Response body -> f (Response body)
responseVersion = (HttpVersion -> f HttpVersion)
-> Response body -> f (Response body)
forall body (f :: * -> *).
Functor f =>
(HttpVersion -> f HttpVersion)
-> Response body -> f (Response body)
TH.responseVersion
responseHeader :: HeaderName
-> Traversal' (Response body) ByteString
= HeaderName
-> (ByteString -> f ByteString)
-> Response body
-> f (Response body)
HeaderName -> Traversal' (Response body) ByteString
forall body. HeaderName -> Traversal' (Response body) ByteString
TH.responseHeader
responseHeaders :: Lens' (Response body) ResponseHeaders
= ([Header] -> f [Header]) -> Response body -> f (Response body)
forall body (f :: * -> *).
Functor f =>
([Header] -> f [Header]) -> Response body -> f (Response body)
TH.responseHeaders
responseLink :: ByteString
-> ByteString
-> Fold (Response body) Link
responseLink :: forall body. ByteString -> ByteString -> Fold (Response body) Link
responseLink = ByteString
-> ByteString
-> (Link -> f Link)
-> Response body
-> f (Response body)
ByteString -> ByteString -> Fold (Response body) Link
forall body. ByteString -> ByteString -> Fold (Response body) Link
TH.responseLink
responseBody :: Lens (Response body0) (Response body1) body0 body1
responseBody :: forall body0 body1 (f :: * -> *).
Functor f =>
(body0 -> f body1) -> Response body0 -> f (Response body1)
responseBody = (body0 -> f body1) -> Response body0 -> f (Response body1)
forall body0 body1 (f :: * -> *).
Functor f =>
(body0 -> f body1) -> Response body0 -> f (Response body1)
TH.responseBody
responseCookie :: ByteString
-> Fold (Response body) Cookie
responseCookie :: forall body. ByteString -> Fold (Response body) Cookie
responseCookie = ByteString
-> (Cookie -> f Cookie) -> Response body -> f (Response body)
ByteString -> Fold (Response body) Cookie
forall body. ByteString -> Fold (Response body) Cookie
TH.responseCookie
responseCookieJar :: Lens' (Response body) CookieJar
responseCookieJar :: forall body (f :: * -> *).
Functor f =>
(CookieJar -> f CookieJar) -> Response body -> f (Response body)
responseCookieJar = (CookieJar -> f CookieJar) -> Response body -> f (Response body)
forall body (f :: * -> *).
Functor f =>
(CookieJar -> f CookieJar) -> Response body -> f (Response body)
TH.responseCookieJar
hrFinalRequest :: Lens' (HistoriedResponse body) Request
hrFinalRequest :: forall body (f :: * -> *).
Functor f =>
(Request -> f Request)
-> HistoriedResponse body -> f (HistoriedResponse body)
hrFinalRequest = (Request -> f Request)
-> HistoriedResponse body -> f (HistoriedResponse body)
forall body (f :: * -> *).
Functor f =>
(Request -> f Request)
-> HistoriedResponse body -> f (HistoriedResponse body)
TH.hrFinalRequest
hrFinalResponse :: Lens' (HistoriedResponse body) (Response body)
hrFinalResponse :: forall body (f :: * -> *).
Functor f =>
(Response body -> f (Response body))
-> HistoriedResponse body -> f (HistoriedResponse body)
hrFinalResponse = (Response body -> f (Response body))
-> HistoriedResponse body -> f (HistoriedResponse body)
forall body1 body2 (f :: * -> *).
Functor f =>
(Response body1 -> f (Response body2))
-> HistoriedResponse body1 -> f (HistoriedResponse body2)
TH.hrFinalResponse
hrRedirects :: Lens' (HistoriedResponse body) [(Request, Response L.ByteString)]
hrRedirects :: forall body (f :: * -> *).
Functor f =>
([(Request, Response ByteString)]
-> f [(Request, Response ByteString)])
-> HistoriedResponse body -> f (HistoriedResponse body)
hrRedirects = ([(Request, Response ByteString)]
-> f [(Request, Response ByteString)])
-> HistoriedResponse body -> f (HistoriedResponse body)
forall body (f :: * -> *).
Functor f =>
([(Request, Response ByteString)]
-> f [(Request, Response ByteString)])
-> HistoriedResponse body -> f (HistoriedResponse body)
TH.hrRedirects
statusCode :: Lens' Status Int
statusCode :: Lens' Status Int
statusCode = (Int -> f Int) -> Status -> f Status
Lens' Status Int
TH.statusCode
statusMessage :: Lens' Status ByteString
statusMessage :: Lens' Status ByteString
statusMessage = (ByteString -> f ByteString) -> Status -> f Status
Lens' Status ByteString
TH.statusMessage
linkURL :: Lens' Link ByteString
linkURL :: Lens' Link ByteString
linkURL = (ByteString -> f ByteString) -> Link -> f Link
Lens' Link ByteString
TH.linkURL
linkParams :: Lens' Link [(ByteString, ByteString)]
linkParams :: Lens' Link [(ByteString, ByteString)]
linkParams = ([(ByteString, ByteString)] -> f [(ByteString, ByteString)])
-> Link -> f Link
Lens' Link [(ByteString, ByteString)]
TH.linkParams
partName :: Lens' Part Text
partName :: Lens' Part Text
partName = (Text -> f Text) -> Part -> f Part
forall (m :: * -> *) (f :: * -> *).
Functor f =>
(Text -> f Text) -> PartM m -> f (PartM m)
TH.partName
partFileName :: Lens' Part (Maybe String)
partFileName :: Lens' Part (Maybe String)
partFileName = (Maybe String -> f (Maybe String)) -> Part -> f Part
forall (m :: * -> *) (f :: * -> *).
Functor f =>
(Maybe String -> f (Maybe String)) -> PartM m -> f (PartM m)
TH.partFilename
partContentType :: Traversal' Part (Maybe MimeType)
partContentType :: Traversal' Part (Maybe ByteString)
partContentType = (Maybe ByteString -> f (Maybe ByteString)) -> Part -> f Part
forall (m :: * -> *) (f :: * -> *).
Functor f =>
(Maybe ByteString -> f (Maybe ByteString))
-> PartM m -> f (PartM m)
TH.partContentType
partGetBody :: Lens' Part (IO RequestBody)
partGetBody :: Lens' Part (IO RequestBody)
partGetBody = (IO RequestBody -> f (IO RequestBody)) -> Part -> f Part
forall (m1 :: * -> *) (m2 :: * -> *) (f :: * -> *).
Functor f =>
(m1 RequestBody -> f (m2 RequestBody)) -> PartM m1 -> f (PartM m2)
TH.partGetBody
atto :: Parser a -> Fold ByteString a
atto :: forall a. Parser a -> Fold ByteString a
atto Parser a
p = (ByteString -> Either String a) -> Fold ByteString a
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
folding (Parser a -> ByteString -> Either String a
forall a. Parser a -> ByteString -> Either String a
parseOnly Parser a
p)
atto_ :: Parser a -> Fold ByteString a
atto_ :: forall a. Parser a -> Fold ByteString a
atto_ Parser a
p = Parser a -> Fold ByteString a
forall a. Parser a -> Fold ByteString a
atto (Parser a
p Parser a -> Parser ByteString () -> Parser a
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString ()
forall t. Chunk t => Parser t ()
endOfInput)