Skip to content

Commit f5ffdc7

Browse files
authored
Merge pull request #899 from phadej/response-body-refactor
Refactor servant-client-core Response+StreamingResponse
2 parents ff26894 + f4fc2b3 commit f5ffdc7

File tree

9 files changed

+27
-18
lines changed

9 files changed

+27
-18
lines changed

servant-client-core/src/Servant/Client/Core.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,8 @@ module Servant.Client.Core
4040

4141

4242
-- * Response
43-
, Response(..)
43+
, Response
44+
, GenResponse (..)
4445
, RunClient(..)
4546
, module Servant.Client.Core.Internal.BaseUrl
4647
, StreamingResponse(..)

servant-client-core/src/Servant/Client/Core/Internal/HasClient.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -269,7 +269,8 @@ instance OVERLAPPABLE_
269269
, requestMethod = reflectMethod (Proxy :: Proxy method)
270270
}
271271
return . buildFromStream $ ResultStream $ \k ->
272-
runStreamingResponse sresp $ \(_status,_headers,_httpversion,reader) -> do
272+
runStreamingResponse sresp $ \gres -> do
273+
let reader = responseBody gres
273274
let unrender = unrenderFrames (Proxy :: Proxy framing) (Proxy :: Proxy a)
274275
loop bs = do
275276
res <- BL.fromStrict <$> reader

servant-client-core/src/Servant/Client/Core/Internal/Request.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,9 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DeriveDataTypeable #-}
33
{-# LANGUAGE DeriveFunctor #-}
4+
{-# LANGUAGE DeriveFoldable #-}
5+
{-# LANGUAGE DeriveTraversable #-}
46
{-# LANGUAGE DeriveGeneric #-}
5-
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
67
{-# LANGUAGE MultiParamTypeClasses #-}
78
{-# LANGUAGE RankNTypes #-}
89
{-# LANGUAGE OverloadedStrings #-}
@@ -65,14 +66,15 @@ type Request = RequestF Builder.Builder
6566
newtype RequestBody = RequestBodyLBS LBS.ByteString
6667
deriving (Eq, Ord, Read, Show, Typeable)
6768

68-
data Response = Response
69+
data GenResponse a = Response
6970
{ responseStatusCode :: Status
70-
, responseBody :: LBS.ByteString
7171
, responseHeaders :: Seq.Seq Header
7272
, responseHttpVersion :: HttpVersion
73-
} deriving (Eq, Show, Generic, Typeable)
73+
, responseBody :: a
74+
} deriving (Eq, Show, Generic, Typeable, Functor, Foldable, Traversable)
7475

75-
data StreamingResponse = StreamingResponse { runStreamingResponse :: forall a. ((Status, Seq.Seq Header, HttpVersion, IO BS.ByteString) -> IO a) -> IO a }
76+
type Response = GenResponse LBS.ByteString
77+
newtype StreamingResponse = StreamingResponse { runStreamingResponse :: forall a. (GenResponse (IO BS.ByteString) -> IO a) -> IO a }
7678

7779
-- A GET request to the top-level path
7880
defaultRequest :: Request

servant-client-core/src/Servant/Client/Core/Internal/RunClient.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import Network.HTTP.Media (MediaType, matches,
1818
import Servant.API (MimeUnrender,
1919
contentTypes,
2020
mimeUnrender)
21-
import Servant.Client.Core.Internal.Request (Request, Response (..),
21+
import Servant.Client.Core.Internal.Request (Request, Response, GenResponse (..),
2222
StreamingResponse (..),
2323
ServantError (..))
2424

servant-client-core/src/Servant/Client/Core/Reexport.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,11 @@ module Servant.Client.Core.Reexport
55
(
66
-- * HasClient
77
HasClient(..)
8+
89
-- * Response (for @Raw@)
9-
, Response(..)
10+
, Response
11+
, StreamingResponse
12+
, GenResponse(..)
1013

1114
-- * Generic Client
1215
, ClientLike(..)

servant-client/servant-client.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,9 @@ library
4949
, time >= 1.4.2 && < 1.9
5050
, transformers >= 0.3.0.0 && < 0.6
5151

52+
if !impl(ghc >= 8.0)
53+
build-depends: semigroups >=0.18.3 && <0.19
54+
5255
-- Servant dependencies
5356
build-depends:
5457
servant-client-core == 0.12.*

servant-client/src/Servant/Client.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
2+
13
-- | This module provides 'client' which can automatically generate
24
-- querying functions for each endpoint just from the type representing your
35
-- API.
@@ -10,5 +12,5 @@ module Servant.Client
1012
, module Servant.Client.Core.Reexport
1113
) where
1214

13-
import Servant.Client.Internal.HttpClient
1415
import Servant.Client.Core.Reexport
16+
import Servant.Client.Internal.HttpClient

servant-client/src/Servant/Client/Internal/HttpClient.hs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -8,11 +8,8 @@
88
{-# LANGUAGE OverloadedStrings #-}
99
{-# LANGUAGE ScopedTypeVariables #-}
1010
{-# LANGUAGE TypeFamilies #-}
11-
12-
-- | @http-client@-based client requests executor
1311
module Servant.Client.Internal.HttpClient where
1412

15-
1613
import Prelude ()
1714
import Prelude.Compat
1815

@@ -31,7 +28,7 @@ import qualified Data.ByteString.Lazy as BSL
3128
import Data.Foldable (toList, for_)
3229
import Data.Functor.Alt (Alt (..))
3330
import Data.Maybe (maybeToList)
34-
import Data.Monoid ((<>))
31+
import Data.Semigroup ((<>))
3532
import Data.Proxy (Proxy (..))
3633
import Data.Sequence (fromList)
3734
import Data.String (fromString)
@@ -151,10 +148,10 @@ performStreamingRequest req = do
151148
status_code = statusCode status
152149
unless (status_code >= 200 && status_code < 300) $ do
153150
b <- BSL.fromChunks <$> Client.brConsume (Client.responseBody r)
154-
throw $ FailureResponse $ Response status b (fromList $ Client.responseHeaders r) (Client.responseVersion r)
155-
k (status, fromList $ Client.responseHeaders r, Client.responseVersion r, Client.responseBody r)
151+
throw $ FailureResponse $ clientResponseToResponse r { Client.responseBody = b }
152+
k (clientResponseToResponse r)
156153

157-
clientResponseToResponse :: Client.Response BSL.ByteString -> Response
154+
clientResponseToResponse :: Client.Response a -> GenResponse a
158155
clientResponseToResponse r = Response
159156
{ responseStatusCode = Client.responseStatus r
160157
, responseBody = Client.responseBody r

servant/servant.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ library
7171
build-depends:
7272
base >= 4.7 && < 4.11
7373
, bytestring >= 0.10.4.0 && < 0.11
74-
, mtl >= 2.0.1 && < 2.3
74+
, mtl >= 2.1 && < 2.3
7575
, text >= 1.2.3.0 && < 1.3
7676

7777
if !impl(ghc >= 8.0)

0 commit comments

Comments
 (0)