Skip to content

Commit

Permalink
Expose more constructors for RequestBody.
Browse files Browse the repository at this point in the history
    Mimicking http-client's RequestBody.
  • Loading branch information
jkarni committed Mar 19, 2018
1 parent 37482d6 commit 26c6c0e
Showing 1 changed file with 23 additions and 16 deletions.
39 changes: 23 additions & 16 deletions servant-client-core/src/Servant/Client/Core/Internal/Request.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,25 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

module Servant.Client.Core.Internal.Request where

import Prelude ()
import Prelude.Compat

import Control.Monad.Catch (Exception)
import qualified Data.ByteString.Builder as Builder
import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as Builder
import qualified Data.ByteString.Lazy as LBS
import Data.Int (Int64)
import Data.Semigroup ((<>))
import qualified Data.Sequence as Seq
import Data.Text (Text)
Expand Down Expand Up @@ -58,13 +59,19 @@ data RequestF a = Request
, requestHeaders :: Seq.Seq Header
, requestHttpVersion :: HttpVersion
, requestMethod :: Method
} deriving (Eq, Show, Functor, Generic, Typeable)
} deriving (Generic, Typeable)

type Request = RequestF Builder.Builder

-- | The request body. Currently only lazy ByteStrings are supported.
newtype RequestBody = RequestBodyLBS LBS.ByteString
deriving (Eq, Ord, Read, Show, Typeable)
-- | The request body. A replica of the @http-client@ @RequestBody@.
data RequestBody
= 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
{ responseStatusCode :: Status
Expand Down

0 comments on commit 26c6c0e

Please sign in to comment.