Refactor servant-client(-core)

- Rename GenResponse to ResponseF (analogous to RequestF)
- add NFData Headers
- Make Request and Response bodies be SourceIO,
  i.e. move conversions into specific implementations
This commit is contained in:
Oleg Grenrus 2019-02-06 12:12:56 +02:00
parent 2071042ebb
commit 4fab471c29
13 changed files with 236 additions and 155 deletions

View file

@ -137,7 +137,7 @@ And we continue by turning http-client's `Response` into servant's `Response`,
and calling the continuation. We should get a `Pure` value. and calling the continuation. We should get a `Pure` value.
```haskell ```haskell
let res = I.clientResponseToResponse res' let res = I.clientResponseToResponse id res'
case k res of case k res of
Pure n -> Pure n ->

View file

@ -39,10 +39,12 @@ library
Servant.Client.Core.Internal.Auth Servant.Client.Core.Internal.Auth
Servant.Client.Core.Internal.BaseUrl Servant.Client.Core.Internal.BaseUrl
Servant.Client.Core.Internal.BasicAuth Servant.Client.Core.Internal.BasicAuth
Servant.Client.Core.Internal.ClientError
Servant.Client.Core.Internal.ClientF Servant.Client.Core.Internal.ClientF
Servant.Client.Core.Internal.Generic Servant.Client.Core.Internal.Generic
Servant.Client.Core.Internal.HasClient Servant.Client.Core.Internal.HasClient
Servant.Client.Core.Internal.Request Servant.Client.Core.Internal.Request
Servant.Client.Core.Internal.Response
Servant.Client.Core.Internal.RunClient Servant.Client.Core.Internal.RunClient
-- Bundled with GHC: Lower bound to not force re-installs -- Bundled with GHC: Lower bound to not force re-installs

View file

@ -41,7 +41,7 @@ module Servant.Client.Core
-- * Response -- * Response
, Response , Response
, GenResponse (..) , ResponseF (..)
, RunClient(..) , RunClient(..)
, module Servant.Client.Core.Internal.BaseUrl , module Servant.Client.Core.Internal.BaseUrl
-- ** Streaming -- ** Streaming
@ -64,4 +64,6 @@ import Servant.Client.Core.Internal.BasicAuth
import Servant.Client.Core.Internal.Generic import Servant.Client.Core.Internal.Generic
import Servant.Client.Core.Internal.HasClient import Servant.Client.Core.Internal.HasClient
import Servant.Client.Core.Internal.Request import Servant.Client.Core.Internal.Request
import Servant.Client.Core.Internal.Response
import Servant.Client.Core.Internal.ClientError
import Servant.Client.Core.Internal.RunClient import Servant.Client.Core.Internal.RunClient

View file

@ -0,0 +1,82 @@
{-# 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.ClientError where
import Prelude ()
import Prelude.Compat
import Control.DeepSeq
(NFData (..))
import Control.Exception
(SomeException (..))
import Control.Monad.Catch
(Exception)
import qualified Data.ByteString as BS
import Data.Text
(Text)
import Data.Typeable
(Typeable, typeOf)
import GHC.Generics
(Generic)
import Network.HTTP.Media (MediaType)
import Network.HTTP.Types ()
import Servant.Client.Core.Internal.BaseUrl
import Servant.Client.Core.Internal.Request
import Servant.Client.Core.Internal.Response
-- | A type representing possible errors in a request
--
-- Note that this type substantially changed in 0.12.
data ServantError =
-- | The server returned an error response including the
-- failing request. 'requestPath' includes the 'BaseUrl' and the
-- path of the request.
FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response
-- | The body could not be decoded at the expected type
| DecodeFailure Text Response
-- | The content-type of the response is not supported
| UnsupportedContentType MediaType Response
-- | The content-type header is invalid
| InvalidContentTypeHeader Response
-- | There was a connection error, and no response was received
| ConnectionError SomeException
deriving (Show, Generic, Typeable)
instance Eq ServantError where
FailureResponse req res == FailureResponse req' res' = req == req' && res == res'
DecodeFailure t r == DecodeFailure t' r' = t == t' && r == r'
UnsupportedContentType mt r == UnsupportedContentType mt' r' = mt == mt' && r == r'
InvalidContentTypeHeader r == InvalidContentTypeHeader r' = r == r'
ConnectionError exc == ConnectionError exc' = eqSomeException exc exc'
where
-- returns true, if type of exception is the same
eqSomeException (SomeException a) (SomeException b) = typeOf a == typeOf b
-- prevent wild card blindness
FailureResponse {} == _ = False
DecodeFailure {} == _ = False
UnsupportedContentType {} == _ = False
InvalidContentTypeHeader {} == _ = False
ConnectionError {} == _ = False
instance Exception ServantError
-- | Note: an exception in 'ConnectionError' might not be evaluated fully,
-- We only 'rnf' its 'show'ed value.
instance NFData ServantError where
rnf (FailureResponse req res) = rnf req `seq` rnf res
rnf (DecodeFailure err res) = rnf err `seq` rnf res
rnf (UnsupportedContentType mt' res) = mediaTypeRnf mt' `seq` rnf res
rnf (InvalidContentTypeHeader res) = rnf res
rnf (ConnectionError err) = err `seq` rnf (show err)

View file

@ -2,6 +2,8 @@
module Servant.Client.Core.Internal.ClientF where module Servant.Client.Core.Internal.ClientF where
import Servant.Client.Core.Internal.Request import Servant.Client.Core.Internal.Request
import Servant.Client.Core.Internal.Response
import Servant.Client.Core.Internal.ClientError
data ClientF a data ClientF a
= RunRequest Request (Response -> a) = RunRequest Request (Response -> a)

View file

@ -16,9 +16,6 @@ module Servant.Client.Core.Internal.HasClient where
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat
import Control.Concurrent.MVar
(modifyMVar, newMVar)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Foldable import Data.Foldable
(toList) (toList)
@ -50,11 +47,12 @@ import Servant.API.ContentTypes
(contentTypes) (contentTypes)
import Servant.API.Modifiers import Servant.API.Modifiers
(FoldRequired, RequiredArgument, foldRequiredArgument) (FoldRequired, RequiredArgument, foldRequiredArgument)
import qualified Servant.Types.SourceT as S
import Servant.Client.Core.Internal.Auth import Servant.Client.Core.Internal.Auth
import Servant.Client.Core.Internal.BasicAuth import Servant.Client.Core.Internal.BasicAuth
import Servant.Client.Core.Internal.ClientError
import Servant.Client.Core.Internal.Request import Servant.Client.Core.Internal.Request
import Servant.Client.Core.Internal.Response
import Servant.Client.Core.Internal.RunClient import Servant.Client.Core.Internal.RunClient
-- * Accessing APIs as a Client -- * Accessing APIs as a Client
@ -283,7 +281,7 @@ instance {-# OVERLAPPABLE #-}
clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do
let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk
framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender' framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender'
return $ fromSourceIO $ framingUnrender' $ S.fromAction BS.null (responseBody gres) return $ fromSourceIO $ framingUnrender' $ responseBody gres
where where
req' = req req' = req
{ requestAccept = fromList [contentType (Proxy :: Proxy ct)] { requestAccept = fromList [contentType (Proxy :: Proxy ct)]
@ -552,7 +550,7 @@ instance
clientWithRoute pm Proxy req body clientWithRoute pm Proxy req body
= clientWithRoute pm (Proxy :: Proxy api) = clientWithRoute pm (Proxy :: Proxy api)
$ setRequestBody (RequestBodyStreamChunked givesPopper) (contentType ctypeP) req $ setRequestBody (RequestBodySource sourceIO) (contentType ctypeP) req
where where
ctypeP = Proxy :: Proxy ctype ctypeP = Proxy :: Proxy ctype
framingP = Proxy :: Proxy framing framingP = Proxy :: Proxy framing
@ -562,28 +560,6 @@ instance
(mimeRender ctypeP :: chunk -> BL.ByteString) (mimeRender ctypeP :: chunk -> BL.ByteString)
(toSourceIO body) (toSourceIO body)
-- not pretty.
givesPopper :: (IO BS.ByteString -> IO ()) -> IO ()
givesPopper needsPopper = S.unSourceT sourceIO $ \step0 -> do
ref <- newMVar step0
-- Note sure we need locking, but it's feels safer.
let popper :: IO BS.ByteString
popper = modifyMVar ref nextBs
needsPopper popper
nextBs S.Stop = return (S.Stop, BS.empty)
nextBs (S.Error err) = fail err
nextBs (S.Skip s) = nextBs s
nextBs (S.Effect ms) = ms >>= nextBs
nextBs (S.Yield lbs s) = case BL.toChunks lbs of
[] -> nextBs s
(x:xs) | BS.null x -> nextBs step'
| otherwise -> return (step', x)
where
step' = S.Yield (BL.fromChunks xs) s
-- | Make the querying function append @path@ to the request path. -- | Make the querying function append @path@ to the request path.
instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where
type Client m (path :> api) = Client m api type Client m (path :> api) = Client m api

View file

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFunctor #-}
@ -17,10 +16,6 @@ import Prelude.Compat
import Control.DeepSeq import Control.DeepSeq
(NFData (..)) (NFData (..))
import Control.Exception
(SomeException (..))
import Control.Monad.Catch
(Exception)
import Data.Bifoldable import Data.Bifoldable
(Bifoldable (..)) (Bifoldable (..))
import Data.Bifunctor import Data.Bifunctor
@ -30,8 +25,6 @@ import Data.Bitraversable
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as Builder 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
@ -40,64 +33,16 @@ import Data.Text
import Data.Text.Encoding import Data.Text.Encoding
(encodeUtf8) (encodeUtf8)
import Data.Typeable import Data.Typeable
(Typeable, typeOf) (Typeable)
import GHC.Generics import GHC.Generics
(Generic) (Generic)
import Network.HTTP.Media import Network.HTTP.Media
(MediaType, mainType, parameters, subType) (MediaType, mainType, parameters, subType)
import Network.HTTP.Types import Network.HTTP.Types
(Header, HeaderName, HttpVersion (..), Method, QueryItem, (Header, HeaderName, HttpVersion (..), Method, QueryItem,
Status (..), http11, methodGet) http11, methodGet)
import Servant.API import Servant.API
(ToHttpApiData, toEncodedUrlPiece, toHeader) (ToHttpApiData, toEncodedUrlPiece, toHeader, SourceIO)
import Servant.Client.Core.Internal.BaseUrl
(BaseUrl)
-- | A type representing possible errors in a request
--
-- Note that this type substantially changed in 0.12.
data ServantError =
-- | The server returned an error response including the
-- failing request. 'requestPath' includes the 'BaseUrl' and the
-- path of the request.
FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response
-- | The body could not be decoded at the expected type
| DecodeFailure Text Response
-- | The content-type of the response is not supported
| UnsupportedContentType MediaType Response
-- | The content-type header is invalid
| InvalidContentTypeHeader Response
-- | There was a connection error, and no response was received
| ConnectionError SomeException
deriving (Show, Generic, Typeable)
instance Eq ServantError where
FailureResponse req res == FailureResponse req' res' = req == req' && res == res'
DecodeFailure t r == DecodeFailure t' r' = t == t' && r == r'
UnsupportedContentType mt r == UnsupportedContentType mt' r' = mt == mt' && r == r'
InvalidContentTypeHeader r == InvalidContentTypeHeader r' = r == r'
ConnectionError exc == ConnectionError exc' = eqSomeException exc exc'
where
-- returns true, if type of exception is the same
eqSomeException (SomeException a) (SomeException b) = typeOf a == typeOf b
-- prevent wild card blindness
FailureResponse {} == _ = False
DecodeFailure {} == _ = False
UnsupportedContentType {} == _ = False
InvalidContentTypeHeader {} == _ = False
ConnectionError {} == _ = False
instance Exception ServantError
-- | Note: an exception in 'ConnectionError' might not be evaluated fully,
-- We only 'rnf' its 'show'ed value.
instance NFData ServantError where
rnf (FailureResponse req res) = rnf req `seq` rnf res
rnf (DecodeFailure err res) = rnf err `seq` rnf res
rnf (UnsupportedContentType mt' res) = mediaTypeRnf mt' `seq` rnf res
rnf (InvalidContentTypeHeader res) = rnf res
rnf (ConnectionError err) = err `seq` rnf (show err)
mediaTypeRnf :: MediaType -> () mediaTypeRnf :: MediaType -> ()
mediaTypeRnf mt = mediaTypeRnf mt =
@ -143,31 +88,13 @@ type Request = RequestF RequestBody Builder.Builder
data RequestBody data RequestBody
= RequestBodyLBS LBS.ByteString = RequestBodyLBS LBS.ByteString
| RequestBodyBS BS.ByteString | RequestBodyBS BS.ByteString
| RequestBodyBuilder Int64 Builder.Builder | RequestBodySource (SourceIO LBS.ByteString)
| RequestBodyStream Int64 ((IO BS.ByteString -> IO ()) -> IO ())
| RequestBodyStreamChunked ((IO BS.ByteString -> IO ()) -> IO ())
| RequestBodyIO (IO RequestBody)
deriving (Generic, Typeable) deriving (Generic, Typeable)
data GenResponse a = Response instance Show RequestBody where
{ responseStatusCode :: Status showsPrec d (RequestBodyLBS lbs) = showParen (d > 10)
, responseHeaders :: Seq.Seq Header $ showString "RequestBodyLBS "
, responseHttpVersion :: HttpVersion . showsPrec 11 lbs
, responseBody :: a
} deriving (Eq, Show, Generic, Typeable, Functor, Foldable, Traversable)
instance NFData a => NFData (GenResponse a) where
rnf (Response sc hs hv body) =
rnfStatus sc `seq`
rnf hs `seq`
rnfHttpVersion hv `seq`
rnf body
where
rnfStatus (Status code msg) = rnf code `seq` rnf msg
rnfHttpVersion (HttpVersion _ _) = () -- HttpVersion fields are strict
type Response = GenResponse LBS.ByteString
type StreamingResponse = GenResponse (IO BS.ByteString)
-- A GET request to the top-level path -- A GET request to the top-level path
defaultRequest :: Request defaultRequest :: Request

View file

@ -0,0 +1,49 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Servant.Client.Core.Internal.Response where
import Prelude ()
import Prelude.Compat
import Control.DeepSeq
(NFData (..))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Sequence as Seq
import Data.Typeable
(Typeable)
import GHC.Generics
(Generic)
import Network.HTTP.Types
(Header, HttpVersion (..), Status (..))
import Servant.API.Stream
(SourceIO)
data ResponseF a = Response
{ responseStatusCode :: Status
, responseHeaders :: Seq.Seq Header
, responseHttpVersion :: HttpVersion
, responseBody :: a
} deriving (Eq, Show, Generic, Typeable, Functor, Foldable, Traversable)
instance NFData a => NFData (ResponseF a) where
rnf (Response sc hs hv body) =
rnfStatus sc `seq`
rnf hs `seq`
rnfHttpVersion hv `seq`
rnf body
where
rnfStatus (Status code msg) = rnf code `seq` rnf msg
rnfHttpVersion (HttpVersion _ _) = () -- HttpVersion fields are strict
type Response = ResponseF LBS.ByteString
type StreamingResponse = ResponseF (SourceIO BS.ByteString)

View file

@ -25,8 +25,8 @@ import Servant.API
import Servant.Client.Core.Internal.ClientF import Servant.Client.Core.Internal.ClientF
import Servant.Client.Core.Internal.Request import Servant.Client.Core.Internal.Request
(GenResponse (..), Request, Response, ServantError (..), import Servant.Client.Core.Internal.Response
StreamingResponse) import Servant.Client.Core.Internal.ClientError
class Monad m => RunClient m where class Monad m => RunClient m where
-- | How to make a request. -- | How to make a request.

View file

@ -9,7 +9,7 @@ module Servant.Client.Core.Reexport
-- * Response (for @Raw@) -- * Response (for @Raw@)
, Response , Response
, StreamingResponse , StreamingResponse
, GenResponse(..) , ResponseF(..)
-- * Generic Client -- * Generic Client
, ClientLike(..) , ClientLike(..)
@ -30,4 +30,5 @@ module Servant.Client.Core.Reexport
import Servant.Client.Core.Internal.BaseUrl import Servant.Client.Core.Internal.BaseUrl
import Servant.Client.Core.Internal.Generic import Servant.Client.Core.Internal.Generic
import Servant.Client.Core.Internal.HasClient import Servant.Client.Core.Internal.HasClient
import Servant.Client.Core.Internal.Request import Servant.Client.Core.Internal.Response
import Servant.Client.Core.Internal.ClientError

View file

@ -14,6 +14,9 @@ module Servant.Client.Internal.HttpClient where
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat
import Control.Concurrent.MVar
(modifyMVar, newMVar)
import qualified Data.ByteString as BS
import Control.Concurrent.STM.TVar import Control.Concurrent.STM.TVar
import Control.Exception import Control.Exception
import Control.Monad import Control.Monad
@ -52,7 +55,6 @@ import Data.Sequence
(fromList) (fromList)
import Data.String import Data.String
(fromString) (fromString)
import qualified Data.Text as T
import Data.Time.Clock import Data.Time.Clock
(UTCTime, getCurrentTime) (UTCTime, getCurrentTime)
import GHC.Generics import GHC.Generics
@ -62,6 +64,7 @@ import Network.HTTP.Types
(hContentType, renderQuery, statusCode) (hContentType, renderQuery, statusCode)
import Servant.Client.Core import Servant.Client.Core
import qualified Servant.Types.SourceT as S
import qualified Network.HTTP.Client as Client import qualified Network.HTTP.Client as Client
-- | The environment in which a request is run. -- | The environment in which a request is run.
@ -167,7 +170,7 @@ performRequest req = do
response <- maybe (requestWithoutCookieJar m request) (requestWithCookieJar m request) cookieJar' response <- maybe (requestWithoutCookieJar m request) (requestWithCookieJar m request) cookieJar'
let status = Client.responseStatus response let status = Client.responseStatus response
status_code = statusCode status status_code = statusCode status
ourResponse = clientResponseToResponse response ourResponse = clientResponseToResponse id response
unless (status_code >= 200 && status_code < 300) $ unless (status_code >= 200 && status_code < 300) $
throwError $ mkFailureResponse burl req ourResponse throwError $ mkFailureResponse burl req ourResponse
return ourResponse return ourResponse
@ -197,16 +200,16 @@ performRequest req = do
fReq = Client.hrFinalRequest responses fReq = Client.hrFinalRequest responses
fRes = Client.hrFinalResponse responses fRes = Client.hrFinalResponse responses
mkFailureResponse :: BaseUrl -> Request -> GenResponse BSL.ByteString -> ServantError mkFailureResponse :: BaseUrl -> Request -> ResponseF BSL.ByteString -> ServantError
mkFailureResponse burl request = mkFailureResponse burl request =
FailureResponse (bimap (const ()) f request) FailureResponse (bimap (const ()) f request)
where where
f b = (burl, BSL.toStrict $ toLazyByteString b) f b = (burl, BSL.toStrict $ toLazyByteString b)
clientResponseToResponse :: Client.Response a -> GenResponse a clientResponseToResponse :: (a -> b) -> Client.Response a -> ResponseF b
clientResponseToResponse r = Response clientResponseToResponse f r = Response
{ responseStatusCode = Client.responseStatus r { responseStatusCode = Client.responseStatus r
, responseBody = Client.responseBody r , responseBody = f (Client.responseBody r)
, responseHeaders = fromList $ Client.responseHeaders r , responseHeaders = fromList $ Client.responseHeaders r
, responseHttpVersion = Client.responseVersion r , responseHttpVersion = Client.responseVersion r
} }
@ -239,15 +242,32 @@ requestToClientRequest burl r = Client.defaultRequest
convertBody bd = case bd of convertBody bd = case bd of
RequestBodyLBS body' -> Client.RequestBodyLBS body' RequestBodyLBS body' -> Client.RequestBodyLBS body'
RequestBodyBS body' -> Client.RequestBodyBS body' RequestBodyBS body' -> Client.RequestBodyBS body'
RequestBodyBuilder size body' -> Client.RequestBodyBuilder size body' RequestBodySource sourceIO -> Client.RequestBodyStreamChunked givesPopper
RequestBodyStream size body' -> Client.RequestBodyStream size body' where
RequestBodyStreamChunked body' -> Client.RequestBodyStreamChunked body' givesPopper :: (IO BS.ByteString -> IO ()) -> IO ()
RequestBodyIO body' -> Client.RequestBodyIO (convertBody <$> body') givesPopper needsPopper = S.unSourceT sourceIO $ \step0 -> do
ref <- newMVar step0
-- Note sure we need locking, but it's feels safer.
let popper :: IO BS.ByteString
popper = modifyMVar ref nextBs
needsPopper popper
nextBs S.Stop = return (S.Stop, BS.empty)
nextBs (S.Error err) = fail err
nextBs (S.Skip s) = nextBs s
nextBs (S.Effect ms) = ms >>= nextBs
nextBs (S.Yield lbs s) = case BSL.toChunks lbs of
[] -> nextBs s
(x:xs) | BS.null x -> nextBs step'
| otherwise -> return (step', x)
where
step' = S.Yield (BSL.fromChunks xs) s
(body, contentTypeHdr) = case requestBody r of (body, contentTypeHdr) = case requestBody r of
Nothing -> (Client.RequestBodyLBS "", Nothing) Nothing -> (Client.RequestBodyBS "", Nothing)
Just (body', typ) Just (body', typ) -> (convertBody body', Just (hContentType, renderHeader typ))
-> (convertBody body', Just (hContentType, renderHeader typ))
isSecure = case baseUrlScheme burl of isSecure = case baseUrlScheme burl of
Http -> False Http -> False

View file

@ -35,6 +35,7 @@ import Control.Monad.Reader
import Control.Monad.STM import Control.Monad.STM
(atomically) (atomically)
import Control.Monad.Trans.Except import Control.Monad.Trans.Except
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
import Data.Foldable import Data.Foldable
(for_) (for_)
@ -53,8 +54,9 @@ import qualified Network.HTTP.Client as Client
import Servant.Client.Core import Servant.Client.Core
import Servant.Client.Internal.HttpClient import Servant.Client.Internal.HttpClient
(ClientEnv (..), catchConnectionError, (ClientEnv (..), catchConnectionError,
clientResponseToResponse, mkClientEnv, requestToClientRequest, clientResponseToResponse, mkClientEnv, mkFailureResponse,
mkFailureResponse) requestToClientRequest)
import qualified Servant.Types.SourceT as S
-- | Generates a set of client functions for an API. -- | Generates a set of client functions for an API.
@ -165,7 +167,7 @@ performRequest req = do
atomically $ modifyTVar' cj (fst . Client.updateCookieJar response request now') atomically $ modifyTVar' cj (fst . Client.updateCookieJar response request now')
let status = Client.responseStatus response let status = Client.responseStatus response
status_code = statusCode status status_code = statusCode status
ourResponse = clientResponseToResponse response ourResponse = clientResponseToResponse id response
unless (status_code >= 200 && status_code < 300) $ unless (status_code >= 200 && status_code < 300) $
throwError $ mkFailureResponse burl req ourResponse throwError $ mkFailureResponse burl req ourResponse
return ourResponse return ourResponse
@ -183,7 +185,7 @@ performWithStreamingRequest req k = do
-- we throw FailureResponse in IO :( -- we throw FailureResponse in IO :(
unless (status_code >= 200 && status_code < 300) $ do unless (status_code >= 200 && status_code < 300) $ do
b <- BSL.fromChunks <$> Client.brConsume (Client.responseBody res) b <- BSL.fromChunks <$> Client.brConsume (Client.responseBody res)
throwIO $ mkFailureResponse burl req (clientResponseToResponse res { Client.responseBody = b }) throwIO $ mkFailureResponse burl req (clientResponseToResponse (const b) res)
x <- k (clientResponseToResponse res) x <- k (clientResponseToResponse (S.fromAction BS.null) res)
k1 x k1 x

View file

@ -35,6 +35,8 @@ module Servant.API.ResponseHeaders
, HList(..) , HList(..)
) where ) where
import Control.DeepSeq
(NFData (..))
import Data.ByteString.Char8 as BS import Data.ByteString.Char8 as BS
(ByteString, init, pack, unlines) (ByteString, init, pack, unlines)
import qualified Data.CaseInsensitive as CI import qualified Data.CaseInsensitive as CI
@ -60,16 +62,32 @@ data Headers ls a = Headers { getResponse :: a
-- ^ HList of headers. -- ^ HList of headers.
} deriving (Functor) } deriving (Functor)
instance (NFDataHList ls, NFData a) => NFData (Headers ls a) where
rnf (Headers x hdrs) = rnf x `seq` rnf hdrs
data ResponseHeader (sym :: Symbol) a data ResponseHeader (sym :: Symbol) a
= Header a = Header a
| MissingHeader | MissingHeader
| UndecodableHeader ByteString | UndecodableHeader ByteString
deriving (Typeable, Eq, Show, Functor) deriving (Typeable, Eq, Show, Functor)
instance NFData a => NFData (ResponseHeader sym a) where
rnf MissingHeader = ()
rnf (UndecodableHeader bs) = rnf bs
rnf (Header x) = rnf x
data HList a where data HList a where
HNil :: HList '[] HNil :: HList '[]
HCons :: ResponseHeader h x -> HList xs -> HList (Header h x ': xs) HCons :: ResponseHeader h x -> HList xs -> HList (Header h x ': xs)
class NFDataHList xs where rnfHList :: HList xs -> ()
instance NFDataHList '[] where rnfHList HNil = ()
instance (y ~ Header h x, NFData x, NFDataHList xs) => NFDataHList (y ': xs) where
rnfHList (HCons h xs) = rnf h `seq` rnfHList xs
instance NFDataHList xs => NFData (HList xs) where
rnf = rnfHList
type family HeaderValMap (f :: * -> *) (xs :: [*]) where type family HeaderValMap (f :: * -> *) (xs :: [*]) where
HeaderValMap f '[] = '[] HeaderValMap f '[] = '[]
HeaderValMap f (Header h x ': xs) = Header h (f x) ': HeaderValMap f xs HeaderValMap f (Header h x ': xs) = Header h (f x) ': HeaderValMap f xs