Skip to content

Commit 72b7abb

Browse files
authored
Client middleware (#1720)
1 parent 185600a commit 72b7abb

File tree

6 files changed

+148
-7
lines changed

6 files changed

+148
-7
lines changed

.github/workflows/master.yml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@ jobs:
1515
os: [ubuntu-latest]
1616
cabal: ["3.10"]
1717
ghc:
18-
- "8.6.5"
1918
- "8.8.4"
2019
- "8.10.7"
2120
- "9.0.2"

changelog.d/1720

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
synopsis: Client Middleware
2+
prs: #1720
3+
4+
description: {
5+
6+
Clients now support real middleware of type `(Request -> ClientM Response) -> Request -> ClientM Response` which can be configured in `ClientEnv`.
7+
This allows access to raw request and response data. It can also be used to control how/when/if actual requests are performed.
8+
Middleware can be chained with function composition `mid1 . mid2 . mid3`.
9+
10+
}

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

Lines changed: 18 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# LANGUAGE RankNTypes #-}
1010
{-# LANGUAGE ScopedTypeVariables #-}
1111
{-# LANGUAGE TypeFamilies #-}
12+
{-# LANGUAGE NamedFieldPuns #-}
1213
module Servant.Client.Internal.HttpClient where
1314

1415
import Prelude ()
@@ -86,11 +87,22 @@ data ClientEnv
8687
-- 1. 'makeClientRequest' exists to allow overriding operational semantics e.g. 'responseTimeout' per request,
8788
-- If you need global modifications, you should use 'managerModifyRequest'
8889
-- 2. the 'cookieJar', if defined, is being applied after 'makeClientRequest' is called.
90+
, middleware :: ClientMiddleware
8991
}
9092

93+
type ClientApplication = Request -> ClientM Response
94+
95+
type ClientMiddleware = ClientApplication -> ClientApplication
96+
9197
-- | 'ClientEnv' smart constructor.
9298
mkClientEnv :: Client.Manager -> BaseUrl -> ClientEnv
93-
mkClientEnv mgr burl = ClientEnv mgr burl Nothing defaultMakeClientRequest
99+
mkClientEnv manager baseUrl = ClientEnv
100+
{ manager
101+
, baseUrl
102+
, cookieJar = Nothing
103+
, makeClientRequest = defaultMakeClientRequest
104+
, middleware = id
105+
}
94106

95107
-- | Generates a set of client functions for an API.
96108
--
@@ -153,15 +165,18 @@ instance Alt ClientM where
153165
a <!> b = a `catchError` \_ -> b
154166

155167
instance RunClient ClientM where
156-
runRequestAcceptStatus = performRequest
168+
runRequestAcceptStatus statuses req = do
169+
ClientEnv {middleware} <- ask
170+
let oldApp = performRequest statuses
171+
middleware oldApp req
157172
throwClientError = throwError
158173

159174
runClientM :: ClientM a -> ClientEnv -> IO (Either ClientError a)
160175
runClientM cm env = runExceptT $ flip runReaderT env $ unClientM cm
161176

162177
performRequest :: Maybe [Status] -> Request -> ClientM Response
163178
performRequest acceptStatus req = do
164-
ClientEnv m burl cookieJar' createClientRequest <- ask
179+
ClientEnv m burl cookieJar' createClientRequest _ <- ask
165180
clientRequest <- liftIO $ createClientRequest burl req
166181
request <- case cookieJar' of
167182
Nothing -> pure clientRequest

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -140,7 +140,7 @@ runClientM cm env = withClientM cm env (evaluate . force)
140140
performRequest :: Maybe [Status] -> Request -> ClientM Response
141141
performRequest acceptStatus req = do
142142
-- TODO: should use Client.withResponse here too
143-
ClientEnv m burl cookieJar' createClientRequest <- ask
143+
ClientEnv m burl cookieJar' createClientRequest _ <- ask
144144
clientRequest <- liftIO $ createClientRequest burl req
145145
request <- case cookieJar' of
146146
Nothing -> pure clientRequest
@@ -175,7 +175,7 @@ performRequest acceptStatus req = do
175175
-- | TODO: support UVerb ('acceptStatus' argument, like in 'performRequest' above).
176176
performWithStreamingRequest :: Request -> (StreamingResponse -> IO a) -> ClientM a
177177
performWithStreamingRequest req k = do
178-
ClientEnv m burl cookieJar' createClientRequest <- ask
178+
ClientEnv m burl cookieJar' createClientRequest _ <- ask
179179
clientRequest <- liftIO $ createClientRequest burl req
180180
request <- case cookieJar' of
181181
Nothing -> pure clientRequest
Lines changed: 117 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,117 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE ConstraintKinds #-}
3+
{-# LANGUAGE DataKinds #-}
4+
{-# LANGUAGE FlexibleContexts #-}
5+
{-# LANGUAGE FlexibleInstances #-}
6+
{-# LANGUAGE GADTs #-}
7+
{-# LANGUAGE MultiParamTypeClasses #-}
8+
{-# LANGUAGE OverloadedStrings #-}
9+
{-# LANGUAGE PolyKinds #-}
10+
{-# LANGUAGE ScopedTypeVariables #-}
11+
{-# LANGUAGE TypeFamilies #-}
12+
{-# LANGUAGE UndecidableInstances #-}
13+
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14+
{-# OPTIONS_GHC -fno-warn-orphans #-}
15+
{-# OPTIONS_GHC -freduction-depth=100 #-}
16+
17+
module Servant.MiddlewareSpec (spec) where
18+
19+
import Control.Arrow
20+
( left,
21+
)
22+
import Control.Concurrent (newEmptyMVar, putMVar, takeMVar)
23+
import Control.Exception (Exception, throwIO, try)
24+
import Control.Monad.IO.Class
25+
import Data.ByteString.Builder (toLazyByteString)
26+
import Data.IORef (modifyIORef, newIORef, readIORef)
27+
import Data.Monoid ()
28+
import Prelude.Compat
29+
import Servant.Client
30+
import Servant.Client.Core (RequestF (..))
31+
import Servant.Client.Internal.HttpClient (ClientMiddleware)
32+
import Servant.ClientTestUtils
33+
import Test.Hspec
34+
import Prelude ()
35+
36+
runClientWithMiddleware :: ClientM a -> ClientMiddleware -> BaseUrl -> IO (Either ClientError a)
37+
runClientWithMiddleware x mid baseUrl' =
38+
runClientM x ((mkClientEnv manager' baseUrl') {middleware = mid})
39+
40+
data CustomException = CustomException deriving (Show, Eq)
41+
42+
instance Exception CustomException
43+
44+
spec :: Spec
45+
spec = beforeAll (startWaiApp server) $ afterAll endWaiApp $ do
46+
it "Raw request and response can be accessed in middleware" $ \(_, baseUrl) -> do
47+
mvarReq <- newEmptyMVar
48+
mvarResp <- newEmptyMVar
49+
50+
let mid :: ClientMiddleware
51+
mid oldApp req = do
52+
-- "Log" request
53+
liftIO $ putMVar mvarReq req
54+
-- perform request
55+
resp <- oldApp req
56+
-- "Log" response
57+
liftIO $ putMVar mvarResp resp
58+
pure resp
59+
60+
-- Same as without middleware
61+
left show <$> runClientWithMiddleware getGet mid baseUrl `shouldReturn` Right alice
62+
63+
-- Access some raw request data
64+
req <- takeMVar mvarReq
65+
toLazyByteString (requestPath req) `shouldBe` "/get"
66+
67+
-- Access some raw response data
68+
resp <- takeMVar mvarResp
69+
responseBody resp `shouldBe` "{\"_age\":42,\"_name\":\"Alice\"}"
70+
71+
it "errors can be thrown in middleware" $ \(_, baseUrl) -> do
72+
let mid :: ClientMiddleware
73+
mid oldApp req = do
74+
-- perform request
75+
resp <- oldApp req
76+
-- throw error
77+
_ <- liftIO $ throwIO CustomException
78+
pure resp
79+
80+
try (runClientWithMiddleware getGet mid baseUrl) `shouldReturn` Left CustomException
81+
82+
it "runs in the expected order" $ \(_, baseUrl) -> do
83+
ref <- newIORef []
84+
85+
let mid1 :: ClientMiddleware
86+
mid1 oldApp req = do
87+
liftIO $ modifyIORef ref (\xs -> xs <> ["req1"])
88+
resp <- oldApp req
89+
liftIO $ modifyIORef ref (\xs -> xs <> ["resp1"])
90+
pure resp
91+
92+
let mid2 :: ClientMiddleware
93+
mid2 oldApp req = do
94+
liftIO $ modifyIORef ref (\xs -> xs <> ["req2"])
95+
resp <- oldApp req
96+
liftIO $ modifyIORef ref (\xs -> xs <> ["resp2"])
97+
pure resp
98+
99+
let mid3 :: ClientMiddleware
100+
mid3 oldApp req = do
101+
liftIO $ modifyIORef ref (\xs -> xs <> ["req3"])
102+
resp <- oldApp req
103+
liftIO $ modifyIORef ref (\xs -> xs <> ["resp3"])
104+
pure resp
105+
106+
let mid :: ClientMiddleware
107+
mid = mid1 . mid2 . mid3
108+
-- \^ Composition in "reverse order".
109+
-- It is equivalent to the following, which is more intuitive:
110+
-- mid :: ClientMiddleware
111+
-- mid oldApp = mid1 (mid2 (mid3 oldApp))
112+
113+
-- Same as without middleware
114+
left show <$> runClientWithMiddleware getGet mid baseUrl `shouldReturn` Right alice
115+
116+
ref <- readIORef ref
117+
ref `shouldBe` ["req1", "req2", "req3", "resp3", "resp2", "resp1"]

servant-client/test/Servant/SuccessSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -154,7 +154,7 @@ successSpec = beforeAll (startWaiApp server) $ afterAll endWaiApp $ do
154154
it "Stores Cookie in CookieJar after a redirect" $ \(_, baseUrl) -> do
155155
mgr <- C.newManager C.defaultManagerSettings
156156
cj <- atomically . newTVar $ C.createCookieJar []
157-
_ <- runClientM (getRedirectWithCookie HTTP.methodGet) (ClientEnv mgr baseUrl (Just cj) defaultMakeClientRequest)
157+
_ <- runClientM (getRedirectWithCookie HTTP.methodGet) (ClientEnv mgr baseUrl (Just cj) defaultMakeClientRequest id)
158158
cookie <- listToMaybe . C.destroyCookieJar <$> atomically (readTVar cj)
159159
C.cookie_name <$> cookie `shouldBe` Just "testcookie"
160160
C.cookie_value <$> cookie `shouldBe` Just "test"

0 commit comments

Comments
 (0)