{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, FlexibleInstances, GADTs,
OverloadedStrings, RankNTypes, RecordWildCards, DefaultSignatures #-}
module Network.Wreq.Internal.Types
(
Options(..)
, Mgr
, Auth(..)
, AWSAuthVersion(..)
, ResponseChecker
, Payload(..)
, Postable(..)
, Putable(..)
, FormParam(..)
, FormValue(..)
, ContentType
, Link(..)
, JSONError(..)
, Req(..)
, reqURL
, Session(..)
, Run
, RunHistory
, Body(..)
, CacheEntry(..)
) where
import Control.Exception (Exception)
import Data.IORef (IORef)
import Data.Monoid ((<>), mconcat)
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Data.Typeable (Typeable)
import Network.HTTP.Client (CookieJar, Manager, ManagerSettings, Request,
RequestBody)
import Network.HTTP.Client.Internal (Response, Proxy)
import Network.HTTP.Types (Header)
import Prelude hiding (head)
import qualified Data.ByteString.Char8 as S
import qualified Data.ByteString.Lazy as L
import qualified Network.HTTP.Client as HTTP
type ContentType = S.ByteString
type Mgr = Either ManagerSettings Manager
data Options = Options {
Options -> Mgr
manager :: Mgr
, Options -> Maybe Proxy
proxy :: Maybe Proxy
, Options -> Maybe Auth
auth :: Maybe Auth
, :: [Header]
, Options -> [(Text, Text)]
params :: [(Text, Text)]
, Options -> Int
redirects :: Int
, Options -> Maybe CookieJar
cookies :: Maybe CookieJar
, Options -> Maybe ResponseChecker
checkResponse :: Maybe ResponseChecker
} deriving (Typeable)
type ResponseChecker = Request -> Response HTTP.BodyReader -> IO ()
data Auth = BasicAuth S.ByteString S.ByteString
| OAuth2Bearer S.ByteString
| OAuth2Token S.ByteString
| AWSAuth AWSAuthVersion S.ByteString S.ByteString (Maybe S.ByteString)
| AWSFullAuth AWSAuthVersion S.ByteString S.ByteString (Maybe S.ByteString) (Maybe (S.ByteString, S.ByteString))
| OAuth1 S.ByteString S.ByteString S.ByteString S.ByteString
deriving (Auth -> Auth -> Bool
(Auth -> Auth -> Bool) -> (Auth -> Auth -> Bool) -> Eq Auth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Auth -> Auth -> Bool
$c/= :: Auth -> Auth -> Bool
== :: Auth -> Auth -> Bool
$c== :: Auth -> Auth -> Bool
Eq, Int -> Auth -> ShowS
[Auth] -> ShowS
Auth -> String
(Int -> Auth -> ShowS)
-> (Auth -> String) -> ([Auth] -> ShowS) -> Show Auth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Auth] -> ShowS
$cshowList :: [Auth] -> ShowS
show :: Auth -> String
$cshow :: Auth -> String
showsPrec :: Int -> Auth -> ShowS
$cshowsPrec :: Int -> Auth -> ShowS
Show, Typeable)
data AWSAuthVersion = AWSv4
deriving (AWSAuthVersion -> AWSAuthVersion -> Bool
(AWSAuthVersion -> AWSAuthVersion -> Bool)
-> (AWSAuthVersion -> AWSAuthVersion -> Bool) -> Eq AWSAuthVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AWSAuthVersion -> AWSAuthVersion -> Bool
$c/= :: AWSAuthVersion -> AWSAuthVersion -> Bool
== :: AWSAuthVersion -> AWSAuthVersion -> Bool
$c== :: AWSAuthVersion -> AWSAuthVersion -> Bool
Eq, Int -> AWSAuthVersion -> ShowS
[AWSAuthVersion] -> ShowS
AWSAuthVersion -> String
(Int -> AWSAuthVersion -> ShowS)
-> (AWSAuthVersion -> String)
-> ([AWSAuthVersion] -> ShowS)
-> Show AWSAuthVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AWSAuthVersion] -> ShowS
$cshowList :: [AWSAuthVersion] -> ShowS
show :: AWSAuthVersion -> String
$cshow :: AWSAuthVersion -> String
showsPrec :: Int -> AWSAuthVersion -> ShowS
$cshowsPrec :: Int -> AWSAuthVersion -> ShowS
Show)
instance Show Options where
show :: Options -> String
show (Options{Int
[(Text, Text)]
[Header]
Maybe CookieJar
Maybe Proxy
Maybe Auth
Maybe ResponseChecker
Mgr
checkResponse :: Maybe ResponseChecker
cookies :: Maybe CookieJar
redirects :: Int
params :: [(Text, Text)]
headers :: [Header]
auth :: Maybe Auth
proxy :: Maybe Proxy
manager :: Mgr
checkResponse :: Options -> Maybe ResponseChecker
cookies :: Options -> Maybe CookieJar
redirects :: Options -> Int
params :: Options -> [(Text, Text)]
headers :: Options -> [Header]
auth :: Options -> Maybe Auth
proxy :: Options -> Maybe Proxy
manager :: Options -> Mgr
..}) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
String
"Options { "
, String
"manager = ", case Mgr
manager of
Left ManagerSettings
_ -> String
"Left _"
Right Manager
_ -> String
"Right _"
, String
", proxy = ", Maybe Proxy -> String
forall a. Show a => a -> String
show Maybe Proxy
proxy
, String
", auth = ", Maybe Auth -> String
forall a. Show a => a -> String
show Maybe Auth
auth
, String
", headers = ", [Header] -> String
forall a. Show a => a -> String
show [Header]
headers
, String
", params = ", [(Text, Text)] -> String
forall a. Show a => a -> String
show [(Text, Text)]
params
, String
", redirects = ", Int -> String
forall a. Show a => a -> String
show Int
redirects
, String
", cookies = ", Maybe CookieJar -> String
forall a. Show a => a -> String
show Maybe CookieJar
cookies
, String
" }"
]
class Postable a where
postPayload :: a -> Request -> IO Request
default postPayload :: Putable a => a -> Request -> IO Request
postPayload = a -> Request -> IO Request
forall a. Putable a => a -> Request -> IO Request
putPayload
class Putable a where
putPayload :: a -> Request -> IO Request
data Payload where
Raw :: ContentType -> RequestBody -> Payload
deriving (Typeable)
class FormValue a where
renderFormValue :: a -> S.ByteString
data FormParam where
(:=) :: (FormValue v) => S.ByteString -> v -> FormParam
instance Show FormParam where
show :: FormParam -> String
show (ByteString
a := v
b) = ByteString -> String
forall a. Show a => a -> String
show ByteString
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" := " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (v -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue v
b)
infixr 3 :=
data JSONError = JSONError String
deriving (Int -> JSONError -> ShowS
[JSONError] -> ShowS
JSONError -> String
(Int -> JSONError -> ShowS)
-> (JSONError -> String)
-> ([JSONError] -> ShowS)
-> Show JSONError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JSONError] -> ShowS
$cshowList :: [JSONError] -> ShowS
show :: JSONError -> String
$cshow :: JSONError -> String
showsPrec :: Int -> JSONError -> ShowS
$cshowsPrec :: Int -> JSONError -> ShowS
Show, Typeable)
instance Exception JSONError
data Link = Link {
Link -> ByteString
linkURL :: S.ByteString
, Link -> [(ByteString, ByteString)]
linkParams :: [(S.ByteString, S.ByteString)]
} deriving (Link -> Link -> Bool
(Link -> Link -> Bool) -> (Link -> Link -> Bool) -> Eq Link
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Link -> Link -> Bool
$c/= :: Link -> Link -> Bool
== :: Link -> Link -> Bool
$c== :: Link -> Link -> Bool
Eq, Int -> Link -> ShowS
[Link] -> ShowS
Link -> String
(Int -> Link -> ShowS)
-> (Link -> String) -> ([Link] -> ShowS) -> Show Link
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Link] -> ShowS
$cshowList :: [Link] -> ShowS
show :: Link -> String
$cshow :: Link -> String
showsPrec :: Int -> Link -> ShowS
$cshowsPrec :: Int -> Link -> ShowS
Show, Typeable)
data Req = Req Mgr Request
reqURL :: Req -> S.ByteString
reqURL :: Req -> ByteString
reqURL (Req Mgr
_ Request
req) = [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat [
if Bool
https then ByteString
"https" else ByteString
"http"
, ByteString
"://"
, Request -> ByteString
HTTP.host Request
req
, case (Request -> Int
HTTP.port Request
req, Bool
https) of
(Int
80, Bool
False) -> ByteString
""
(Int
443, Bool
True) -> ByteString
""
(Int
p, Bool
_) -> String -> ByteString
S.pack (Int -> String
forall a. Show a => a -> String
show Int
p)
, Request -> ByteString
HTTP.path Request
req
, case Request -> ByteString
HTTP.queryString Request
req of
ByteString
qs | ByteString -> Bool
S.null ByteString
qs -> ByteString
""
| Bool
otherwise -> ByteString
"?" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
qs
]
where https :: Bool
https = Request -> Bool
HTTP.secure Request
req
type Run body = Req -> IO (Response body)
type RunHistory body = Req -> IO (HTTP.HistoriedResponse body)
data Session = Session {
Session -> Maybe (IORef CookieJar)
seshCookies :: Maybe (IORef CookieJar)
, Session -> Manager
seshManager :: Manager
, Session -> Session -> Run Body -> Run Body
seshRun :: Session -> Run Body -> Run Body
, Session -> Session -> RunHistory Body -> RunHistory Body
seshRunHistory :: Session -> RunHistory Body -> RunHistory Body
}
instance Show Session where
show :: Session -> String
show Session
_ = String
"Session"
data CacheEntry body = CacheEntry {
CacheEntry body -> UTCTime
entryCreated :: UTCTime
, CacheEntry body -> Maybe UTCTime
entryExpires :: Maybe UTCTime
, CacheEntry body -> Response body
entryResponse :: Response body
} deriving (a -> CacheEntry b -> CacheEntry a
(a -> b) -> CacheEntry a -> CacheEntry b
(forall a b. (a -> b) -> CacheEntry a -> CacheEntry b)
-> (forall a b. a -> CacheEntry b -> CacheEntry a)
-> Functor CacheEntry
forall a b. a -> CacheEntry b -> CacheEntry a
forall a b. (a -> b) -> CacheEntry a -> CacheEntry b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CacheEntry b -> CacheEntry a
$c<$ :: forall a b. a -> CacheEntry b -> CacheEntry a
fmap :: (a -> b) -> CacheEntry a -> CacheEntry b
$cfmap :: forall a b. (a -> b) -> CacheEntry a -> CacheEntry b
Functor)
data Body = NoBody
| StringBody L.ByteString
| ReaderBody HTTP.BodyReader
instance Show (CacheEntry body) where
show :: CacheEntry body -> String
show CacheEntry body
_ = String
"CacheEntry"