Expose more constructors for RequestBody.
Mimicking http-client's RequestBody.
This commit is contained in:
parent
37482d69d7
commit
26c6c0ec38
1 changed files with 23 additions and 16 deletions
|
@ -1,14 +1,14 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
{-# LANGUAGE DeriveFunctor #-}
|
{-# LANGUAGE DeriveFoldable #-}
|
||||||
{-# LANGUAGE DeriveFoldable #-}
|
{-# LANGUAGE DeriveFunctor #-}
|
||||||
{-# LANGUAGE DeriveTraversable #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveTraversable #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
|
||||||
module Servant.Client.Core.Internal.Request where
|
module Servant.Client.Core.Internal.Request where
|
||||||
|
|
||||||
|
@ -16,9 +16,10 @@ import Prelude ()
|
||||||
import Prelude.Compat
|
import Prelude.Compat
|
||||||
|
|
||||||
import Control.Monad.Catch (Exception)
|
import Control.Monad.Catch (Exception)
|
||||||
import qualified Data.ByteString.Builder as Builder
|
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
|
import qualified Data.ByteString.Builder as Builder
|
||||||
import qualified Data.ByteString.Lazy as LBS
|
import qualified Data.ByteString.Lazy as LBS
|
||||||
|
import Data.Int (Int64)
|
||||||
import Data.Semigroup ((<>))
|
import Data.Semigroup ((<>))
|
||||||
import qualified Data.Sequence as Seq
|
import qualified Data.Sequence as Seq
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
@ -58,13 +59,19 @@ data RequestF a = Request
|
||||||
, requestHeaders :: Seq.Seq Header
|
, requestHeaders :: Seq.Seq Header
|
||||||
, requestHttpVersion :: HttpVersion
|
, requestHttpVersion :: HttpVersion
|
||||||
, requestMethod :: Method
|
, requestMethod :: Method
|
||||||
} deriving (Eq, Show, Functor, Generic, Typeable)
|
} deriving (Generic, Typeable)
|
||||||
|
|
||||||
type Request = RequestF Builder.Builder
|
type Request = RequestF Builder.Builder
|
||||||
|
|
||||||
-- | The request body. Currently only lazy ByteStrings are supported.
|
-- | The request body. A replica of the @http-client@ @RequestBody@.
|
||||||
newtype RequestBody = RequestBodyLBS LBS.ByteString
|
data RequestBody
|
||||||
deriving (Eq, Ord, Read, Show, Typeable)
|
= RequestBodyLBS LBS.ByteString
|
||||||
|
| RequestBodyBS BS.ByteString
|
||||||
|
| RequestBodyBuilder Int64 Builder.Builder
|
||||||
|
| RequestBodyStream Int64 ((IO BS.ByteString -> IO ()) -> IO ())
|
||||||
|
| RequestBodyStreamChunked ((IO BS.ByteString -> IO ()) -> IO ())
|
||||||
|
| RequestBodyIO (IO RequestBody)
|
||||||
|
deriving (Generic, Typeable)
|
||||||
|
|
||||||
data GenResponse a = Response
|
data GenResponse a = Response
|
||||||
{ responseStatusCode :: Status
|
{ responseStatusCode :: Status
|
||||||
|
|
Loading…
Reference in a new issue