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 (Value, encode)
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 Putable Part where
putPayload a = putPayload [a]
instance Putable [Part] where
putPayload p req =
(\r -> r{method=method req}) <$> formDataBody p req
instance Putable [(S.ByteString, S.ByteString)] where
putPayload ps req =
return $ HTTP.urlEncodedBody ps req {method=method req}
instance Putable (S.ByteString, S.ByteString) where
putPayload p = putPayload [p]
instance Putable [FormParam] where
putPayload ps = putPayload (map f ps)
where f (a := b) = (a, renderFormValue b)
instance Putable FormParam where
putPayload p = putPayload [p]
instance Putable Payload where
putPayload pl =
case pl of
Raw ct rb -> payload ct rb
instance Putable S.ByteString where
putPayload = payload "application/octet-stream" . HTTP.RequestBodyBS
instance Putable L.ByteString where
putPayload = payload "application/octet-stream" . HTTP.RequestBodyLBS
instance Putable Value where
putPayload = payload "application/json" . HTTP.RequestBodyLBS . encode
instance FormValue T.Text where
renderFormValue = T.encodeUtf8
instance FormValue TL.Text where
renderFormValue = T.encodeUtf8 . TL.toStrict
instance FormValue TL.Builder where
renderFormValue = T.encodeUtf8 . TL.toStrict . TL.toLazyText
instance FormValue String where
renderFormValue = T.encodeUtf8 . T.pack
instance FormValue S.ByteString where
renderFormValue = id
instance FormValue L.ByteString where
renderFormValue = S.concat . L.toChunks
instance FormValue Int where renderFormValue = renderFormValue . show
instance FormValue Int8 where renderFormValue = renderFormValue . show
instance FormValue Int16 where renderFormValue = renderFormValue . show
instance FormValue Int32 where renderFormValue = renderFormValue . show
instance FormValue Int64 where renderFormValue = renderFormValue . show
instance FormValue Integer where renderFormValue = renderFormValue . show
instance FormValue Word where renderFormValue = renderFormValue . show
instance FormValue Word8 where renderFormValue = renderFormValue . show
instance FormValue Word16 where renderFormValue = renderFormValue . show
instance FormValue Word32 where renderFormValue = renderFormValue . show
instance FormValue Word64 where renderFormValue = renderFormValue . show
instance FormValue Float where renderFormValue = renderFormValue . show
instance FormValue Double where renderFormValue = renderFormValue . show
instance FormValue () where renderFormValue _ = ""
instance (FormValue a) => FormValue (Maybe a) where
renderFormValue (Just a) = renderFormValue a
renderFormValue Nothing = ""
payload :: S.ByteString -> HTTP.RequestBody -> Request -> IO Request
payload ct body req =
return $ req & Lens.maybeSetHeader "Content-Type" ct
& Lens.requestBody .~ body