Skip to content

Commit 0a4ca09

Browse files
committed
New combinator to return routed path in response headers
This commit introduces a new type-level combinator, `WithRoutingHeader`. It modifies the behaviour of the following sub-API, such that all endpoint of said API return an additional routing header in their response. A routing header is a header that specifies which endpoint the incoming request was routed to. Endpoint are designated by their path, in which `Capture'` and `CaptureAll` combinators are replaced by a capture hint. This header can be used by downstream middlewares to gather information about individual endpoints, since in most cases a routing header uniquely identifies a single endpoint. Example: ```haskell type MyApi = WithRoutingHeader :> "by-id" :> Capture "id" Int :> Get '[JSON] Foo -- GET /by-id/1234 will return a response with the following header: -- ("Servant-Routed-Path", "/by-id/<id:CaptureSingle>") ``` To achieve this, two refactorings were necessary: * Introduce a type `RouterEnv env` to encapsulate the `env` type (as in `Router env a`), which contains a tuple-encoded list of url pieces parsed from the incoming request. This type makes it possible to pass more information throughout the routing process, and the computation of the `Delayed env c` associated with each request. * Introduce a new kind of router, which only modifies the RouterEnv, and doesn't affect the routing process otherwise. `EnvRouter (RouterEnv env -> RouterEnv env) (Router' env a)` This new router is used when encountering the `WithRoutingHeader` combinator in an API, to notify the endpoints of the sub-API that they must produce a routing header (this behaviour is disabled by default).
1 parent baee2be commit 0a4ca09

File tree

9 files changed

+162
-33
lines changed

9 files changed

+162
-33
lines changed

servant-server/servant-server.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ library
4646
Servant.Server.Internal.DelayedIO
4747
Servant.Server.Internal.ErrorFormatter
4848
Servant.Server.Internal.Handler
49+
Servant.Server.Internal.RouterEnv
4950
Servant.Server.Internal.RouteResult
5051
Servant.Server.Internal.Router
5152
Servant.Server.Internal.RoutingApplication

servant-server/src/Servant/Server/Internal.hs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ module Servant.Server.Internal
2626
, module Servant.Server.Internal.ErrorFormatter
2727
, module Servant.Server.Internal.Handler
2828
, module Servant.Server.Internal.Router
29+
, module Servant.Server.Internal.RouterEnv
2930
, module Servant.Server.Internal.RouteResult
3031
, module Servant.Server.Internal.RoutingApplication
3132
, module Servant.Server.Internal.ServerError
@@ -76,7 +77,7 @@ import Servant.API
7677
QueryParam', QueryParams, Raw, ReflectMethod (reflectMethod),
7778
RemoteHost, ReqBody', SBool (..), SBoolI (..), SourceIO,
7879
Stream, StreamBody', Summary, ToSourceIO (..), Vault, Verb,
79-
WithNamedContext, NamedRoutes)
80+
WithNamedContext, WithRoutingHeader, NamedRoutes)
8081
import Servant.API.Generic (GenericMode(..), ToServant, ToServantApi, GServantProduct, toServant, fromServant)
8182
import Servant.API.ContentTypes
8283
(AcceptHeader (..), AllCTRender (..), AllCTUnrender (..),
@@ -103,6 +104,7 @@ import Servant.Server.Internal.ErrorFormatter
103104
import Servant.Server.Internal.Handler
104105
import Servant.Server.Internal.Router
105106
import Servant.Server.Internal.RouteResult
107+
import Servant.Server.Internal.RouterEnv
106108
import Servant.Server.Internal.RoutingApplication
107109
import Servant.Server.Internal.ServerError
108110

@@ -241,6 +243,23 @@ instance (KnownSymbol capture, FromHttpApiData a, Typeable a
241243
formatError = urlParseErrorFormatter $ getContextEntry (mkContextWithErrorFormatter context)
242244
hint = CaptureHint (T.pack $ symbolVal $ Proxy @capture) (typeRep (Proxy :: Proxy [a]))
243245

246+
-- | Using 'WithRoutingHeaders' in one of the endpoints for your API,
247+
-- will automatically add routing headers to the response generated by the server.
248+
--
249+
-- @since 0.20
250+
--
251+
instance ( HasServer api context
252+
, HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters
253+
)
254+
=> HasServer (WithRoutingHeader :> api) context where
255+
256+
type ServerT (WithRoutingHeader :> api) m = ServerT api m
257+
258+
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt s
259+
260+
route _ context d =
261+
EnvRouter enableRoutingHeaders $ route (Proxy :: Proxy api) context d
262+
244263
allowedMethodHead :: Method -> Request -> Bool
245264
allowedMethodHead method request = method == methodGet && requestMethod request == methodHead
246265

@@ -292,7 +311,10 @@ noContentRouter method status action = leafRouter route'
292311
route' env request respond =
293312
runAction (action `addMethodCheck` methodCheck method request)
294313
env request respond $ \ _output ->
295-
Route $ responseLBS status [] ""
314+
let headers = if (shouldReturnRoutedPath env)
315+
then [(hRoutedPathHeader, cs $ routedPathRepr env)]
316+
else []
317+
in Route $ responseLBS status headers ""
296318

297319
instance {-# OVERLAPPABLE #-}
298320
( AllCTRender ctypes a, ReflectMethod method, KnownNat status

servant-server/src/Servant/Server/Internal/Delayed.hs

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -14,11 +14,15 @@ import Control.Monad.Reader
1414
(ask)
1515
import Control.Monad.Trans.Resource
1616
(ResourceT, runResourceT)
17+
import Data.String.Conversions
18+
(cs)
1719
import Network.Wai
18-
(Request, Response)
20+
(Request, Response, mapResponseHeaders)
1921

2022
import Servant.Server.Internal.DelayedIO
2123
import Servant.Server.Internal.Handler
24+
import Servant.Server.Internal.RouterEnv
25+
(RouterEnv (..), hRoutedPathHeader, routedPathRepr)
2226
import Servant.Server.Internal.RouteResult
2327
import Servant.Server.Internal.ServerError
2428

@@ -228,12 +232,12 @@ passToServer Delayed{..} x =
228232
-- This should only be called once per request; otherwise the guarantees about
229233
-- effect and HTTP error ordering break down.
230234
runDelayed :: Delayed env a
231-
-> env
235+
-> RouterEnv env
232236
-> Request
233237
-> ResourceT IO (RouteResult a)
234238
runDelayed Delayed{..} env = runDelayedIO $ do
235239
r <- ask
236-
c <- capturesD env
240+
c <- capturesD $ routerEnv env
237241
methodD
238242
a <- authD
239243
acceptD
@@ -248,7 +252,7 @@ runDelayed Delayed{..} env = runDelayedIO $ do
248252
-- Also takes a continuation for how to turn the
249253
-- result of the delayed server into a response.
250254
runAction :: Delayed env (Handler a)
251-
-> env
255+
-> RouterEnv env
252256
-> Request
253257
-> (RouteResult Response -> IO r)
254258
-> (a -> RouteResult Response)
@@ -261,8 +265,12 @@ runAction action env req respond k = runResourceT $
261265
go (Route a) = liftIO $ do
262266
e <- runHandler a
263267
case e of
264-
Left err -> return . Route $ responseServerError err
265-
Right x -> return $! k x
268+
Left err -> return . Route . withRoutingHeaders $ responseServerError err
269+
Right x -> return $! withRoutingHeaders <$> k x
270+
withRoutingHeaders :: Response -> Response
271+
withRoutingHeaders = if shouldReturnRoutedPath env
272+
then mapResponseHeaders ((hRoutedPathHeader, cs $ routedPathRepr env) :)
273+
else id
266274

267275
{- Note [Existential Record Update]
268276
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

servant-server/src/Servant/Server/Internal/Router.hs

Lines changed: 23 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE DeriveFunctor #-}
33
{-# LANGUAGE GADTs #-}
44
{-# LANGUAGE OverloadedStrings #-}
5+
{-# LANGUAGE TupleSections #-}
56
module Servant.Server.Internal.Router where
67

78
import Prelude ()
@@ -17,29 +18,16 @@ import qualified Data.Map as M
1718
import Data.Text
1819
(Text)
1920
import qualified Data.Text as T
20-
import Data.Typeable
21-
(TypeRep)
2221
import Network.Wai
2322
(Response, pathInfo)
2423
import Servant.Server.Internal.ErrorFormatter
24+
import Servant.Server.Internal.RouterEnv
2525
import Servant.Server.Internal.RouteResult
2626
import Servant.Server.Internal.RoutingApplication
2727
import Servant.Server.Internal.ServerError
2828

2929
type Router env = Router' env RoutingApplication
3030

31-
data CaptureHint = CaptureHint
32-
{ captureName :: Text
33-
, captureType :: TypeRep
34-
}
35-
deriving (Show, Eq)
36-
37-
toCaptureTag :: CaptureHint -> Text
38-
toCaptureTag hint = captureName hint <> "::" <> (T.pack . show) (captureType hint)
39-
40-
toCaptureTags :: [CaptureHint] -> Text
41-
toCaptureTags hints = "<" <> T.intercalate "|" (map toCaptureTag hints) <> ">"
42-
4331
-- | Internal representation of a router.
4432
--
4533
-- The first argument describes an environment type that is
@@ -48,7 +36,7 @@ toCaptureTags hints = "<" <> T.intercalate "|" (map toCaptureTag hints) <> ">"
4836
-- components that can be used to process captures.
4937
--
5038
data Router' env a =
51-
StaticRouter (Map Text (Router' env a)) [env -> a]
39+
StaticRouter (Map Text (Router' env a)) [RouterEnv env -> a]
5240
-- ^ the map contains routers for subpaths (first path component used
5341
-- for lookup and removed afterwards), the list contains handlers
5442
-- for the empty path, to be tried in order
@@ -58,10 +46,13 @@ data Router' env a =
5846
| CaptureAllRouter [CaptureHint] (Router' ([Text], env) a)
5947
-- ^ all path components are passed to the child router in its
6048
-- environment and are removed afterwards
61-
| RawRouter (env -> a)
49+
| RawRouter (RouterEnv env -> a)
6250
-- ^ to be used for routes we do not know anything about
6351
| Choice (Router' env a) (Router' env a)
6452
-- ^ left-biased choice between two routers
53+
| EnvRouter (RouterEnv env -> RouterEnv env) (Router' env a)
54+
-- ^ modifies the environment, and passes it to the child router
55+
-- @since 0.20
6556
deriving Functor
6657

6758
-- | Smart constructor for a single static path component.
@@ -71,7 +62,7 @@ pathRouter t r = StaticRouter (M.singleton t r) []
7162
-- | Smart constructor for a leaf, i.e., a router that expects
7263
-- the empty path.
7364
--
74-
leafRouter :: (env -> a) -> Router' env a
65+
leafRouter :: (RouterEnv env -> a) -> Router' env a
7566
leafRouter l = StaticRouter M.empty [l]
7667

7768
-- | Smart constructor for the choice between routers.
@@ -126,6 +117,7 @@ routerStructure (Choice r1 r2) =
126117
ChoiceStructure
127118
(routerStructure r1)
128119
(routerStructure r2)
120+
routerStructure (EnvRouter _ r) = routerStructure r
129121

130122
-- | Compare the structure of two routers. Ignores capture hints.
131123
--
@@ -182,9 +174,9 @@ tweakResponse f = fmap (\a -> \req cont -> a req (cont . f))
182174

183175
-- | Interpret a router as an application.
184176
runRouter :: NotFoundErrorFormatter -> Router () -> RoutingApplication
185-
runRouter fmt r = runRouterEnv fmt r ()
177+
runRouter fmt r = runRouterEnv fmt r $ emptyEnv ()
186178

187-
runRouterEnv :: NotFoundErrorFormatter -> Router env -> env -> RoutingApplication
179+
runRouterEnv :: NotFoundErrorFormatter -> Router env -> RouterEnv env -> RoutingApplication
188180
runRouterEnv fmt router env request respond =
189181
case router of
190182
StaticRouter table ls ->
@@ -194,24 +186,31 @@ runRouterEnv fmt router env request respond =
194186
[""] -> runChoice fmt ls env request respond
195187
first : rest | Just router' <- M.lookup first table
196188
-> let request' = request { pathInfo = rest }
197-
in runRouterEnv fmt router' env request' respond
189+
newEnv = appendPathPiece (StaticPiece first) env
190+
in runRouterEnv fmt router' newEnv request' respond
198191
_ -> respond $ Fail $ fmt request
199-
CaptureRouter _ router' ->
192+
CaptureRouter hints router' ->
200193
case pathInfo request of
201194
[] -> respond $ Fail $ fmt request
202195
-- This case is to handle trailing slashes.
203196
[""] -> respond $ Fail $ fmt request
204197
first : rest
205198
-> let request' = request { pathInfo = rest }
206-
in runRouterEnv fmt router' (first, env) request' respond
207-
CaptureAllRouter _ router' ->
199+
newEnv = appendPathPiece (CapturePiece hints) env
200+
newEnv' = ((first,) <$> newEnv)
201+
in runRouterEnv fmt router' newEnv' request' respond
202+
CaptureAllRouter hints router' ->
208203
let segments = pathInfo request
209204
request' = request { pathInfo = [] }
210-
in runRouterEnv fmt router' (segments, env) request' respond
205+
newEnv = appendPathPiece (CapturePiece hints) env
206+
newEnv' = ((segments,) <$> newEnv)
207+
in runRouterEnv fmt router' newEnv' request' respond
211208
RawRouter app ->
212209
app env request respond
213210
Choice r1 r2 ->
214211
runChoice fmt [runRouterEnv fmt r1, runRouterEnv fmt r2] env request respond
212+
EnvRouter f router' ->
213+
runRouterEnv fmt router' (f env) request respond
215214

216215
-- | Try a list of routing applications in order.
217216
-- We stop as soon as one fails fatally or succeeds.
Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
{-# LANGUAGE DeriveFunctor #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE RecordWildCards #-}
4+
-- | This module contains the `RouterEnv env` type and associated functions.
5+
-- `RouterEnv env` encapsulates the `env` type (as in `Router env a`),
6+
-- which contains a tuple-encoded list of url pieces parsed from the incoming request.
7+
-- The encapsulation makes it possible to pass more information throughout
8+
-- the routing process, and ultimately to the computation of the `Delayed env c`
9+
-- associated with each request.
10+
-- The type and functions have been designed to be extensible: it should remain easy
11+
-- to add a new field to the record and manipulate it.
12+
--
13+
-- @since 0.20
14+
--
15+
module Servant.Server.Internal.RouterEnv where
16+
17+
import Data.Text
18+
(Text)
19+
import qualified Data.Text as T
20+
import Data.Typeable
21+
(TypeRep)
22+
import Network.HTTP.Types.Header
23+
(HeaderName)
24+
25+
data RouterEnv env = RouterEnv
26+
{ routedPath :: [PathPiece]
27+
, shouldReturnRoutedPath :: Bool
28+
, routerEnv :: env
29+
}
30+
deriving Functor
31+
32+
emptyEnv :: a -> RouterEnv a
33+
emptyEnv v = RouterEnv [] False v
34+
35+
enableRoutingHeaders :: RouterEnv env -> RouterEnv env
36+
enableRoutingHeaders env = env { shouldReturnRoutedPath = True }
37+
38+
routedPathRepr :: RouterEnv env -> Text
39+
routedPathRepr RouterEnv{routedPath = path} =
40+
"/" <> T.intercalate "/" (map go $ reverse path)
41+
where
42+
go (StaticPiece p) = p
43+
go (CapturePiece p) = toCaptureTags p
44+
45+
data PathPiece
46+
= StaticPiece Text
47+
| CapturePiece [CaptureHint]
48+
49+
appendPathPiece :: PathPiece -> RouterEnv a -> RouterEnv a
50+
appendPathPiece p env@RouterEnv{..} = env { routedPath = p:routedPath }
51+
52+
data CaptureHint = CaptureHint
53+
{ captureName :: Text
54+
, captureType :: TypeRep
55+
}
56+
deriving (Show, Eq)
57+
58+
toCaptureTag :: CaptureHint -> Text
59+
toCaptureTag hint = captureName hint <> "::" <> (T.pack . show) (captureType hint)
60+
61+
toCaptureTags :: [CaptureHint] -> Text
62+
toCaptureTags hints = "<" <> T.intercalate "|" (map toCaptureTag hints) <> ">"
63+
64+
hRoutedPathHeader :: HeaderName
65+
hRoutedPathHeader = "Servant-Routed-Path"

servant-server/test/Servant/Server/Internal/RoutingApplicationSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ delayed body srv = Delayed
8080
simpleRun :: Delayed () (Handler ())
8181
-> IO ()
8282
simpleRun d = fmap (either ignoreE id) . try $
83-
runAction d () defaultRequest (\_ -> return ()) (\_ -> FailFatal err500)
83+
runAction d (emptyEnv ()) defaultRequest (\_ -> return ()) (\_ -> FailFatal err500)
8484

8585
where ignoreE :: SomeException -> ()
8686
ignoreE = const ()

servant/servant.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ library
3838
Servant.API.Capture
3939
Servant.API.ContentTypes
4040
Servant.API.Description
41+
Servant.API.Environment
4142
Servant.API.Empty
4243
Servant.API.Experimental.Auth
4344
Servant.API.Fragment

servant/src/Servant/API.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@ module Servant.API (
77
-- | Type-level combinator for alternative endpoints: @':<|>'@
88
module Servant.API.Empty,
99
-- | Type-level combinator for an empty API: @'EmptyAPI'@
10+
module Servant.API.Environment,
11+
-- | Type-level combinators to modify the routing environment: @'WithRoutingHeader'@
1012
module Servant.API.Modifiers,
1113
-- | Type-level modifiers for 'QueryParam', 'Header' and 'ReqBody'.
1214

@@ -96,6 +98,8 @@ import Servant.API.Description
9698
(Description, Summary)
9799
import Servant.API.Empty
98100
(EmptyAPI (..))
101+
import Servant.API.Environment
102+
(WithRoutingHeader)
99103
import Servant.API.Experimental.Auth
100104
(AuthProtect)
101105
import Servant.API.Fragment
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
{-# OPTIONS_HADDOCK not-home #-}
2+
-- | Define API combinator that modify the behaviour of the routing environment.
3+
module Servant.API.Environment (WithRoutingHeader) where
4+
5+
-- | Modify the behaviour of the following sub-API, such that all endpoint of said API
6+
-- return an additional routing header in their response.
7+
-- A routing header is a header that specifies which endpoint the incoming request was
8+
-- routed to. Endpoint are designated by their path, in which @Capture@ combinators are
9+
-- replaced by a capture hint.
10+
-- This header can be used by downstream middlewares to gather information about
11+
-- individual endpoints, since in most cases a routing header uniquely identifies a
12+
-- single endpoint.
13+
--
14+
-- Example:
15+
--
16+
-- >>> type MyApi = WithRoutingHeader :> "by-id" :> Capture "id" Int :> Get '[JSON] Foo
17+
-- >>> -- GET /by-id/1234 will return a response with the following header:
18+
-- >>> -- ("Servant-Routed-Path", "/by-id/<id:CaptureSingle>")
19+
--
20+
-- @since 0.20
21+
--
22+
data WithRoutingHeader
23+
24+
-- $setup
25+
-- >>> import Servant.API
26+
-- >>> import Data.Aeson
27+
-- >>> import Data.Text
28+
-- >>> data Foo
29+
-- >>> instance ToJSON Foo where { toJSON = undefined }

0 commit comments

Comments
 (0)