Copyright | (c) Frederick Pringle 2025 |
---|---|
License | BSD-3-Clause |
Maintainer | freddyjepringle@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Servant.API.Routes
Description
This package provides two things:
- A simple, and probably incomplete, way to represent APIs at the term level.
This is achieved by the
Route
,Routes
,Path
,Param
,HeaderRep
,Request
,Response
andResponses
types. - More interestingly, a way to automatically generate the routes from any Servant API. This is
accomplished using the
HasRoutes
typeclass. You can think of this as being a less sophisticated version ofHasOpenApi
from servant-openapi3, or a more sophisticated version oflayout
from servant-server.
Motivation
Refactoring Servant API types is quite error-prone, especially when you have to move
around lots of :<|>
and :>
. So it's very possible that the route structure could
change in that refactoring, without being caught by the type-checker.
The HasRoutes
class could help as a golden test - run getRoutes
before and after
the refactor, and if they give the same result you can be much more confident that the
refactor didn't introduce difficult bugs.
- Note that
printRoutes
only includes the path, method and query parameters. For more detailed comparison, use the JSON instance ofRoutes
, encode the routes to a file (before and after the refactoring), and use jdiff.
Another use-case is in testing: some Haskellers use type families to modify Servant APIs, for example
to add endpoints or authorisation headers. Types are hard to test, but terms are easy. Use HasRoutes
and run your tests on Routes
.
Synopsis
- data Route
- defRoute :: Method -> Route
- renderRoute :: Route -> Text
- data Routes
- unRoutes :: Routes -> Map Path (Map Method Route)
- pattern Routes :: [Route] -> Routes
- class HasRoutes api where
- printRoutes :: forall api. HasRoutes api => IO ()
- printRoutesJSON :: forall api. HasRoutes api => IO ()
- printRoutesJSONPretty :: forall api. HasRoutes api => IO ()
- data Path
- rootPath :: Path
- prependPathPart :: Text -> Path -> Path
- prependCapturePart :: forall a. Typeable a => Text -> Path -> Path
- prependCaptureAllPart :: forall a. Typeable a => Text -> Path -> Path
- renderPath :: Path -> Text
- data Request
- noRequest :: Request
- oneRequest :: forall a. Typeable a => Request
- allOfRequests :: forall as. AllTypeable as => Request
- data Response
- responseType :: Lens' Response TypeRep
- responseHeaders :: Lens' Response (Set HeaderRep)
- data Responses
- noResponse :: Responses
- oneResponse :: forall a. HasResponse a => Responses
- oneOfResponses :: forall as. AllHasResponse as => Responses
- data HeaderRep
- mkHeaderRep :: forall sym a. (KnownSymbol sym, Typeable a) => HeaderRep
- data Param
- singleParam :: forall s a. (KnownSymbol s, Typeable a) => Param
- arrayElemParam :: forall s a. (KnownSymbol s, Typeable a) => Param
- flagParam :: forall s. KnownSymbol s => Param
- renderParam :: Param -> Text
- data Auth
- basicAuth :: forall realm. KnownSymbol realm => Auth
- customAuth :: forall tag. KnownSymbol tag => Auth
API routes
A simple representation of a single endpoint of an API.
renderRoute :: Route -> Text Source #
Pretty-print a Route
. Note that the output is minimal and doesn't contain all the information
contained in a Route
. For full output, use the ToJSON
instance.
ghci> renderRoute $ defRoute \"POST\" "POST /" ghci> :{ ghci| renderRoute $ ghci| defRoute \"POST\" ghci| & routePath %~ prependPathPart "api/v2" ghci| & routeParams .~ [singleParam @"p1" @T.Text, flagParam @"flag", arrayElemParam @"p2s" @(Maybe Int)] ghci| :} "POST /api/v2?p1=<Text>&flag&p2s=<[Maybe Int]>"
To render all of an API's Route
s as JSON, we need to identify each route by its
path AND its method (since 2 routes can have the same path but different method).
This newtype lets us represent this nested structure.
Automatic generation of routes for Servant API types
Now we can automatically generate a Routes
for any Servant combinator. In most cases
the user should never need to implement HasRoutes
unless they're hacking on Servant or
defining their own combinators.
class HasRoutes api where Source #
Get a simple list of all the routes in an API.
One use-case, which was the original motivation for the class, is refactoring Servant APIs
to use NamedRoutes
. It's a fiddly, repetitive, and error-prone process, and it's very
easy to make small mistakes. A lot of these errors will be caught by the type-checker, e.g.
if the type signature of a handler function doesn't match the ServerT
of its API type.
However there are some errrors that wouldn't be caught by the type-checker, such as missing
out path parts.
For example, if our original API looked like
type API = "api" :> "v2" :> ( "users" :> Get '[JSON] [User] :<|> "user" :> ReqBody '[JSON] UserData :> Post '[JSON] UserId ) server :: Server API server = listUsers :<|> createUser where ...
and we refactored to
data RefactoredAPI mode = RefactoredAPI { listUsers :: mode :- "api" :> "v2" :> "users" :> Get '[JSON] [User] , createUser :: mode :- "user" :> ReqBody '[JSON] UserData :> Post '[JSON] UserId } deriving Generic server :: Server (NamedRoutes RefactoredAPI) server = RefactoredAPI {listUsers, createUser} where ...
Oops! We forgot the "api" :> "v2" :>
in the 2nd sub-endpoint. However, since the ServerT
type
is unaffected by adding or remove path parts, this will still compile.
However, if we use HasRoutes
as a sanity check:
ghci> printRoutes @API GET /api/v2/users POST /api/v2/user ghci> printRoutes @(NamedRoutes RefactoredAPI) GET /api/v2/users POST /user
Much clearer to see the mistake. For more detailed output, use the ToJSON
instance:
ghci> BL.putStrLn . encodePretty $ getRoutes @API [ { "auths": [], "method": "GET", "params": [], "path": "/api/v2/users", "request_body": null, "request_headers": [], "response": "[User]", "response_headers": [] }, { "auths": [], "method": "POST", "params": [], "path": "/api/v2/user", "request_body": "UserData", "request_headers": [], "response": "UserId", "response_headers": [] } ] ghci> BL.putStrLn . encodePretty $ getRoutes @(NamedRoutes RefactoredAPI) [ { "auths": [], "method": "GET", "params": [], "path": "/api/v2/users", "request_body": null, "request_headers": [], "response": "[User]", "response_headers": [] }, { "auths": [], "method": "POST", "params": [], "path": "/user", -- oops! "request_body": "UserData", "request_headers": [], "response": "UserId", "response_headers": [] } ]
Methods
Type-level list of API routes for the given API.
Since TypeApplications
is becoming pervasive, we forego Proxy
here in favour
of getRoutes @API
.
Instances
printRoutes :: forall api. HasRoutes api => IO () Source #
Get all the routes of an API and print them to stdout. See renderRoute
for examples.
printRoutesJSON :: forall api. HasRoutes api => IO () Source #
Same as printRoutes
, but encode the Routes
as JSON before printing to stdout.
For an even prettier version, see printRoutesJSONPretty
.
printRoutesJSONPretty :: forall api. HasRoutes api => IO () Source #
Pretty-encode the Routes
as JSON before printing to stdout.
Types and helper functions
URL paths
Simple representation of a URL path.
prependPathPart :: Text -> Path -> Path Source #
Prepend a simple text path part to an API path.
For example, prependPathPart "api"
will transform /v2/users
to /api/v2/users
.
prependCapturePart :: forall a. Typeable a => Text -> Path -> Path Source #
Prepend a capture path part of a given type to an API path.
Equivalent to
.Capture
name a :>
For example, prependCapturePart @Int "id"
will transform /detail
to /<Int>/detail
.
prependCaptureAllPart :: forall a. Typeable a => Text -> Path -> Path Source #
Prepend a capture-all path part of a given type to an API path.
Equivalent to
.CaptureAll
name a :>
For example, prependCaptureAllPart @Int "id"
will transform /detail
to /<[Int]>/detail
.
renderPath :: Path -> Text Source #
Pretty-print a path, including the leading /
.
Request/response bodies
Requests
A representation of the request body(s) that a Servant endpoint expects.
Under the hood, Request
is a
.
This allows for the possibility that an endpoint might expect the request body
to parse as several different types (multiple Some
TypeRep
ReqBody'
s).
Note that this type doesn't include any information about the headers that an endpoint expects, since those are independent of the request body.
oneRequest :: forall a. Typeable a => Request Source #
The request body can only be of one type. Equivalent to a single
.ReqBody
_ a
allOfRequests :: forall as. AllTypeable as => Request Source #
The endpoint expects the request body to be parsed as multiple (>1) types.
Equivalent to multiple ReqBody
s chained with :>
.
Responses
A representation of one possible response that a Servant endpoint can return.
Currently, the only situation in which multiple Response
s can be returned
is using the UVerb
combinator. This bundles response types together with
response Header
s, so we do the same here.
Instances
ToJSON Response Source # | |
Show Response Source # | |
Eq Response Source # | |
Ord Response Source # | |
Defined in Servant.API.Routes.Internal.Response |
A representation of the response(s) that a Servant endpoint can return.
Under the hood, Responses
is a
.
This allows for the possibility that an endpoint might return one of several
responses, via Some
Response
UVerb
.
Note that a Response
consists of a return body type, as well as the return headers.
noResponse :: Responses Source #
The endpoint will not return a response.
oneResponse :: forall a. HasResponse a => Responses Source #
There is only one possible response. Equivalent to a single
.ReqBody
_ a
oneOfResponses :: forall as. AllHasResponse as => Responses Source #
The endpoint may return one of multiple multiple (>1) responses.
Equivalent to a UVerb
s with more than one type.
Request/response headers
Simple term-level representation of a Header
.
A type-level
should correspond to
Header
(sym :: Symbol
) typ
, where HeaderRep
{ _hName = str, _hType = typRep }str
is the term-level equivalent
of sym
and typRep
is the term-level representation of typ
.
Instances
ToJSON HeaderRep Source # | |
Show HeaderRep Source # | |
Eq HeaderRep Source # | |
Ord HeaderRep Source # | |
Defined in Servant.API.Routes.Internal.Header |
mkHeaderRep :: forall sym a. (KnownSymbol sym, Typeable a) => HeaderRep Source #
Query parameters
singleParam :: forall s a. (KnownSymbol s, Typeable a) => Param Source #
Create a SingleParam
from a Symbol
and a TypeRep
via Typeable
.
arrayElemParam :: forall s a. (KnownSymbol s, Typeable a) => Param Source #
Create an ArrayParam
from a Symbol
and a TypeRep
via Typeable
.
renderParam :: Param -> Text Source #
Pretty-print a Param
. Used by renderRoute
.
Auth schemes
There are 2 variants:
- "Basic" authentication: corresponds to the
BasicAuth
type. Construct withbasicAuth
. - "Custom" authentication: corresponds to the
AuthProtect
type. Construct withcustomAuth
.
basicAuth :: forall realm. KnownSymbol realm => Auth Source #
Create a term-level representation of a "Basic" authentication scheme.
For example:
ghci> toJSON $ basicAuth @"user" String "Basic user"
customAuth :: forall tag. KnownSymbol tag => Auth Source #
Create a term-level representation of a "Custom" authentication scheme, i.e. one that
corresponds to Servant's AuthProtect
combinator.
For example:
ghci> toJSON $ customAuth @"OnlyAdminUsers" String "OnlyAdminUsers"