{-# LANGUAGE FlexibleInstances, OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Network.Wreq.Types
    (
    
      Options(..)
    , Auth(..)
    , AWSAuthVersion(..)
    , ResponseChecker
    
    , Payload(..)
    , Postable(..)
    , Putable(..)
    
    , FormParam(..)
    , FormValue(..)
    
    , ContentType
    , Link(..)
    
    , JSONError(..)
    
    , Req
    , reqURL
    , Run
    ) where
import Control.Lens ((&), (.~))
import Data.Aeson (Encoding, Value, encode)
import Data.Aeson.Encoding (encodingToLazyByteString)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Network.HTTP.Client (Request(method))
import Network.HTTP.Client.MultipartFormData (Part, formDataBody)
import Network.Wreq.Internal.Types
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TL
import qualified Network.HTTP.Client as HTTP
import qualified Network.Wreq.Internal.Lens as Lens
instance Postable Part
instance Postable [Part]
instance Postable [(S.ByteString, S.ByteString)]
instance Postable (S.ByteString, S.ByteString)
instance Postable [FormParam]
instance Postable FormParam
instance Postable Payload
instance Postable S.ByteString
instance Postable L.ByteString
instance Postable Value
instance Postable Encoding
instance Putable Part where
    putPayload :: Part -> Request -> IO Request
putPayload Part
a = [Part] -> Request -> IO Request
forall a. Putable a => a -> Request -> IO Request
putPayload [Part
a]
instance Putable [Part] where
    putPayload :: [Part] -> Request -> IO Request
putPayload [Part]
p Request
req =
        
        (\Request
r -> Request
r{method :: ByteString
method=Request -> ByteString
method Request
req}) (Request -> Request) -> IO Request -> IO Request
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` [Part] -> Request -> IO Request
forall (m :: * -> *). MonadIO m => [Part] -> Request -> m Request
formDataBody [Part]
p Request
req
instance Putable [(S.ByteString, S.ByteString)] where
    putPayload :: [(ByteString, ByteString)] -> Request -> IO Request
putPayload [(ByteString, ByteString)]
ps Request
req =
        
        Request -> IO Request
forall (m :: * -> *) a. Monad m => a -> m a
return (Request -> IO Request) -> Request -> IO Request
forall a b. (a -> b) -> a -> b
$ [(ByteString, ByteString)] -> Request -> Request
HTTP.urlEncodedBody [(ByteString, ByteString)]
ps Request
req {method :: ByteString
method=Request -> ByteString
method Request
req}
instance Putable (S.ByteString, S.ByteString) where
    putPayload :: (ByteString, ByteString) -> Request -> IO Request
putPayload (ByteString, ByteString)
p = [(ByteString, ByteString)] -> Request -> IO Request
forall a. Putable a => a -> Request -> IO Request
putPayload [(ByteString, ByteString)
p]
instance Putable [FormParam] where
    putPayload :: [FormParam] -> Request -> IO Request
putPayload [FormParam]
ps = [(ByteString, ByteString)] -> Request -> IO Request
forall a. Putable a => a -> Request -> IO Request
putPayload ((FormParam -> (ByteString, ByteString))
-> [FormParam] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map FormParam -> (ByteString, ByteString)
f [FormParam]
ps)
      where f :: FormParam -> (ByteString, ByteString)
f (ByteString
a := v
b) = (ByteString
a, v -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue v
b)
instance Putable FormParam where
    putPayload :: FormParam -> Request -> IO Request
putPayload FormParam
p = [FormParam] -> Request -> IO Request
forall a. Putable a => a -> Request -> IO Request
putPayload [FormParam
p]
instance Putable Payload where
    putPayload :: Payload -> Request -> IO Request
putPayload Payload
pl =
      case Payload
pl of
        Raw ByteString
ct RequestBody
rb -> ByteString -> RequestBody -> Request -> IO Request
payload ByteString
ct RequestBody
rb
instance Putable S.ByteString where
    putPayload :: ByteString -> Request -> IO Request
putPayload = ByteString -> RequestBody -> Request -> IO Request
payload ByteString
"application/octet-stream" (RequestBody -> Request -> IO Request)
-> (ByteString -> RequestBody)
-> ByteString
-> Request
-> IO Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
HTTP.RequestBodyBS
instance Putable L.ByteString where
    putPayload :: ByteString -> Request -> IO Request
putPayload = ByteString -> RequestBody -> Request -> IO Request
payload ByteString
"application/octet-stream" (RequestBody -> Request -> IO Request)
-> (ByteString -> RequestBody)
-> ByteString
-> Request
-> IO Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
HTTP.RequestBodyLBS
instance Putable Value where
    putPayload :: Value -> Request -> IO Request
putPayload = ByteString -> RequestBody -> Request -> IO Request
payload ByteString
"application/json" (RequestBody -> Request -> IO Request)
-> (Value -> RequestBody) -> Value -> Request -> IO Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody)
-> (Value -> ByteString) -> Value -> RequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode
instance Putable Encoding where
    putPayload :: Encoding -> Request -> IO Request
putPayload = ByteString -> RequestBody -> Request -> IO Request
payload ByteString
"application/json" (RequestBody -> Request -> IO Request)
-> (Encoding -> RequestBody) -> Encoding -> Request -> IO Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody)
-> (Encoding -> ByteString) -> Encoding -> RequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      Encoding -> ByteString
forall a. Encoding' a -> ByteString
encodingToLazyByteString
instance FormValue T.Text where
    renderFormValue :: Text -> ByteString
renderFormValue = Text -> ByteString
T.encodeUtf8
instance FormValue TL.Text where
    renderFormValue :: Text -> ByteString
renderFormValue = Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (Text -> Text) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict
instance FormValue TL.Builder where
    renderFormValue :: Builder -> ByteString
renderFormValue = Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (Builder -> Text) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TL.toLazyText
instance FormValue String where
    renderFormValue :: String -> ByteString
renderFormValue = Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance FormValue S.ByteString where
    renderFormValue :: ByteString -> ByteString
renderFormValue = ByteString -> ByteString
forall a. a -> a
id
instance FormValue L.ByteString where
    renderFormValue :: ByteString -> ByteString
renderFormValue = [ByteString] -> ByteString
S.concat ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
L.toChunks
instance FormValue Int where renderFormValue :: Int -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
instance FormValue Int8 where renderFormValue :: Int8 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Int8 -> String) -> Int8 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> String
forall a. Show a => a -> String
show
instance FormValue Int16 where renderFormValue :: Int16 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Int16 -> String) -> Int16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> String
forall a. Show a => a -> String
show
instance FormValue Int32 where renderFormValue :: Int32 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Int32 -> String) -> Int32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> String
forall a. Show a => a -> String
show
instance FormValue Int64 where renderFormValue :: Int64 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Int64 -> String) -> Int64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> String
forall a. Show a => a -> String
show
instance FormValue Integer where renderFormValue :: Integer -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString)
-> (Integer -> String) -> Integer -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show
instance FormValue Word where renderFormValue :: Word -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Word -> String) -> Word -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> String
forall a. Show a => a -> String
show
instance FormValue Word8 where renderFormValue :: Word8 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Word8 -> String) -> Word8 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> String
forall a. Show a => a -> String
show
instance FormValue Word16 where renderFormValue :: Word16 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString)
-> (Word16 -> String) -> Word16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> String
forall a. Show a => a -> String
show
instance FormValue Word32 where renderFormValue :: Word32 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString)
-> (Word32 -> String) -> Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> String
forall a. Show a => a -> String
show
instance FormValue Word64 where renderFormValue :: Word64 -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString)
-> (Word64 -> String) -> Word64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> String
forall a. Show a => a -> String
show
instance FormValue Float where renderFormValue :: Float -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString) -> (Float -> String) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> String
forall a. Show a => a -> String
show
instance FormValue Double where renderFormValue :: Double -> ByteString
renderFormValue = String -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue (String -> ByteString)
-> (Double -> String) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> String
forall a. Show a => a -> String
show
instance FormValue () where renderFormValue :: () -> ByteString
renderFormValue ()
_ = ByteString
""
instance (FormValue a) => FormValue (Maybe a) where
    renderFormValue :: Maybe a -> ByteString
renderFormValue (Just a
a) = a -> ByteString
forall a. FormValue a => a -> ByteString
renderFormValue a
a
    renderFormValue Maybe a
Nothing  = ByteString
""
payload :: S.ByteString -> HTTP.RequestBody -> Request -> IO Request
payload :: ByteString -> RequestBody -> Request -> IO Request
payload ByteString
ct RequestBody
body Request
req =
  Request -> IO Request
forall (m :: * -> *) a. Monad m => a -> m a
return (Request -> IO Request) -> Request -> IO Request
forall a b. (a -> b) -> a -> b
$ Request
req Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& HeaderName -> ByteString -> Request -> Request
Lens.maybeSetHeader HeaderName
"Content-Type" ByteString
ct
               Request -> (Request -> Request) -> Request
forall a b. a -> (a -> b) -> b
& (RequestBody -> Identity RequestBody)
-> Request -> Identity Request
Lens' Request RequestBody
Lens.requestBody ((RequestBody -> Identity RequestBody)
 -> Request -> Identity Request)
-> RequestBody -> Request -> Request
forall s t a b. ASetter s t a b -> b -> s -> t
.~ RequestBody
body