servant-routes-0.1.0.0: Generate route descriptions from Servant APIs
Copyright(c) Frederick Pringle 2025
LicenseBSD-3-Clause
Maintainerfreddyjepringle@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.API.Routes

Description

This package provides two things:

  1. 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 and Responses types.
  2. 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 of HasOpenApi from servant-openapi3, or a more sophisticated version of layout 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 of Routes, 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

API routes

data Route Source #

A simple representation of a single endpoint of an API.

defRoute :: Method -> Route Source #

Given a REST Method, create a default Route: root path ("/") with no params, headers, body, auths, or response.

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]>"

data Routes Source #

To render all of an API's Routes 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.

Instances

Instances details
ToJSON Routes Source # 
Instance details

Defined in Servant.API.Routes

Show Routes Source # 
Instance details

Defined in Servant.API.Routes

Eq Routes Source # 
Instance details

Defined in Servant.API.Routes

unRoutes :: Routes -> Map Path (Map Method Route) Source #

Get the underlying Map of a Routes.

pattern Routes :: [Route] -> Routes Source #

A smart constructor that allows us to think of a Routes as simply a list of Routes, whereas it's actually a Map.

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

getRoutes :: [Route] Source #

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

Instances details
HasRoutes EmptyAPI Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes (ToServantApi routes) => HasRoutes (NamedRoutes routes) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes l, HasRoutes r) => HasRoutes (l :<|> r) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

ReflectMethod method => HasRoutes (NoContentVerb method) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (Vault :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol path, HasRoutes api) => HasRoutes (path :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (HttpVersion :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes api, KnownSymbol realm) => HasRoutes (BasicAuth realm usr :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol capture, Typeable a, HasRoutes api) => HasRoutes (Capture' mods capture a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol capture, Typeable a, HasRoutes api) => HasRoutes (CaptureAll capture a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (Description sym :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (Summary sym :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes api, KnownSymbol tag) => HasRoutes (AuthProtect tag :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (Fragment v :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes api, KnownSymbol sym, Typeable (RequiredArgument mods a)) => HasRoutes (Header' mods sym a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (IsSecure :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol sym, HasRoutes api) => HasRoutes (QueryFlag sym :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol sym, Typeable (RequiredArgument mods a), HasRoutes api) => HasRoutes (QueryParam' mods sym a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(KnownSymbol sym, Typeable a, HasRoutes api) => HasRoutes (QueryParams sym a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (RemoteHost :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes api, Typeable a) => HasRoutes (ReqBody' mods list a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(HasRoutes api, Typeable a) => HasRoutes (StreamBody' mods framing ct a :> api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(ReflectMethod method, Typeable a) => HasRoutes (UVerb method ctypes '[a]) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

ReflectMethod method => HasRoutes (UVerb method ctypes ('[] :: [Type])) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(ReflectMethod method, AllHasResponse as, Unique as) => HasRoutes (UVerb method ctypes as) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

HasRoutes api => HasRoutes (WithNamedContext name subContext api) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(ReflectMethod method, GetHeaderReps hs, Typeable a) => HasRoutes (Verb method status ctypes (Headers hs a)) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(ReflectMethod method, Typeable a) => HasRoutes (Verb method status ctypes a) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

(ReflectMethod method, Typeable a) => HasRoutes (Stream method status framing ctype a) Source # 
Instance details

Defined in Servant.API.Routes

Methods

getRoutes :: [Route] Source #

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

data Path Source #

Simple representation of a URL path.

Instances

Instances details
ToJSON Path Source # 
Instance details

Defined in Servant.API.Routes.Internal.Path

Show Path Source # 
Instance details

Defined in Servant.API.Routes.Internal.Path

Eq Path Source # 
Instance details

Defined in Servant.API.Routes.Internal.Path

Methods

(==) :: Path -> Path -> Bool Source #

(/=) :: Path -> Path -> Bool Source #

Ord Path Source # 
Instance details

Defined in Servant.API.Routes.Internal.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

data Request Source #

A representation of the request body(s) that a Servant endpoint expects.

Under the hood, Request is a Some TypeRep. This allows for the possibility that an endpoint might expect the request body to parse as several different types (multiple 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.

noRequest :: Request Source #

The endpoint doesn't expect a 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 ReqBodys chained with :>.

Responses

data Response Source #

A representation of one possible response that a Servant endpoint can return.

Currently, the only situation in which multiple Responses can be returned is using the UVerb combinator. This bundles response types together with response Headers, so we do the same here.

data Responses Source #

A representation of the response(s) that a Servant endpoint can return.

Under the hood, Responses is a Some Response. This allows for the possibility that an endpoint might return one of several responses, via 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 UVerbs with more than one type.

Request/response headers

data HeaderRep Source #

Simple term-level representation of a Header.

A type-level Header (sym :: Symbol) typ should correspond to HeaderRep { _hName = str, _hType = typRep }, where str is the term-level equivalent of sym and typRep is the term-level representation of typ.

mkHeaderRep :: forall sym a. (KnownSymbol sym, Typeable a) => HeaderRep Source #

Convenience function to construct a HeaderRep from sym :: Symbol and a :: Type'.

Query parameters

data Param Source #

Newtype wrapper around servant's Param so we can define a sensible Eq instance for it.

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.

flagParam :: forall s. KnownSymbol s => Param Source #

Create a FlagParam from a Symbol.

renderParam :: Param -> Text Source #

Pretty-print a Param. Used by renderRoute.

Auth schemes

data Auth Source #

There are 2 variants:

Instances

Instances details
ToJSON Auth Source # 
Instance details

Defined in Servant.API.Routes.Internal.Auth

Show Auth Source # 
Instance details

Defined in Servant.API.Routes.Internal.Auth

Eq Auth Source # 
Instance details

Defined in Servant.API.Routes.Internal.Auth

Methods

(==) :: Auth -> Auth -> Bool Source #

(/=) :: Auth -> Auth -> Bool Source #

Ord Auth Source # 
Instance details

Defined in Servant.API.Routes.Internal.Auth

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"