servant/doc/cookbook/namedRoutes/NamedRoutes.lhs

297 lines
9.0 KiB
Plaintext
Raw Normal View History

# Record-based APIs: the nested records case
2022-02-21 11:39:37 +01:00
*Available in Servant 0.19 or higher*
Servant offers a very natural way of constructing APIs with nested records, called `NamedRoutes`.
This cookbook explains how to implement such nested-record-based-APIs using
`NamedRoutes` through the example of a Movie Catalog.
If you don't need the nested aspect of the record-based API, you might want to look at [Record-based
APIs: the simple
case](../generic/Generic.html) cookbook
which covers a simpler implementation in which every endpoint is on the same
level.
2022-02-21 11:39:37 +01:00
First, we start by constructing the domain types of our Movie Catalog.
After, we show you how to implement the API type with the NamedRoutes records.
Lastly, we make a Server and a Client out of the API type.
However, it should be understood that this cookbook does _not_ dwell on the
built-in servant combinators as the [Structuring APIs
](<../structuring-apis/StructuringApis.html>) cookbook already covers that angle.
## Boilerplate time!
First, lets get rid of the the extensions and imports boilerplate in order to focus on our new technique:
```haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
import GHC.Generics ( Generic )
import Data.Aeson ( FromJSON, ToJSON )
import Data.Proxy ( Proxy(..) )
import Network.Wai.Handler.Warp ( run )
import Servant ( NamedRoutes
, Handler, serve )
import Servant.API (Capture, Delete, Get, Put, QueryParam, ReqBody
, JSON, NoContent (..)
, FromHttpApiData (..),ToHttpApiData(..)
, (:>) )
import Servant.API.Generic ( (:-) )
import Servant.Client ( AsClientT, ClientM, client
, (//), (/:) )
import Servant.Client.Generic ()
import Servant.Server ( Application, ServerT )
2022-02-23 07:42:17 +01:00
import Servant.Server.Generic ( AsServer )
2022-02-21 11:39:37 +01:00
```
## Domain context
Now that weve handled the boilerplate, we can dive into our Movie Catalog domain.
Consider a `Movie` constructed from a `Title` and a `Year` of publication.
``` haskell
data Movie = Movie
{ movieId :: MovieId
, title :: Title
, year :: Year
}
deriving stock Generic
deriving anyclass (FromJSON, ToJSON)
type MovieId = String
type Title = String
type Year = Int
```
Lets forget about the deriving stuff for now and think about the API that we want to make.
```
"version" -> Get Version
/
api "list" -> Get [Movie] ?sortBy= Title | Year (sort by the Title or the Year)
\ /
"movies" Get Movie
\ /
Capture MovieId - Put Movie
\
Delete MovieId
```
In this example, we create a very simple endpoint for the Version,
and several complex endpoints that use nested records for the CRUD part of the movie.
So, the URLs would look like
- GET …/version
- GET …/movies/list?sortby=Title
- GET …/movies/<MovieId>/
- PUT …/movies/<MovieId>/
- DELETE …/movies/<MovieId>
### API Type
Now that we have a very clear idea of the API we want to make, we need to transform it into usable Haskell code:
``` haskell
data API mode = API
{ version :: mode :- "version" :> Get '[JSON] Version
, movies :: mode :- "movies" :> NamedRoutes MoviesAPI
} deriving stock Generic
type Version = String -- This will do for the sake of example.
```
Here, we see the first node of our tree. It contains the two branches “version” and “movies” respectively:
The “version” branch is very simple and self-explanatory.
The “movies” branch will contain another node, represented by another record (see above). That is why we need the `NameRoutes` helper.
Note:
The `mode` type parameter indicates into which implementation the records `Generic` representation will be transformed—as a client or as a server. We will discuss that later.
Let's jump into the "movies" subtree node:
``` haskell
data MoviesAPI mode = MoviesAPI
{ list :: mode :- "list" :> QueryParam "SortBy" SortBy :> Get '[JSON] [Movie]
, movie :: mode :- Capture "movieId" MovieId :> NamedRoutes MovieAPI
} deriving stock Generic
data SortBy = Year | Title
instance ToHttpApiData SortBy where
toQueryParam Year = "year"
toQueryParam Title = "title"
instance FromHttpApiData SortBy where
parseQueryParam "year" = Right Year
parseQueryParam "title" = Right Title
parseQueryParam param = Left $ param <> " is not a valid value"
```
So, remember, this type represents the `MoviesAPI` node that weve connected earlier to the main `API` tree.
In this subtree, we illustrated both an endpoint with a **query param** and also, a **capture** with a subtree underneath it.
So, let's go deeper into our API tree.
``` haskell
data MovieAPI mode = MovieAPI
{ get :: mode :- Get '[JSON] (Maybe Movie)
, update :: mode :- ReqBody '[JSON] Movie :> Put '[JSON] NoContent
, delete :: mode :- Delete '[JSON] NoContent
} deriving stock Generic
```
As you can see, we end up implementing the deepest routes of our API.
Small detail: as our main API tree is also a record, we need the `NamedRoutes` helper.
To improve readability, we suggest you create a type alias:
``` haskell
type MovieCatalogAPI = NamedRoutes API
```
That's it, we have our `MovieCatalogAPI` type!
Let's make a server and a client out of it!
## The Server
As you know, we cant talk about a server, without addressing the handlers.
First, we take our handlers…
```haskell
versionHandler :: Handler Version
versionHandler = pure "0.0.1"
movieListHandler :: Maybe SortBy -> Handler [Movie]
movieListHandler _ = pure moviesDB
moviesDB :: [Movie]
moviesDB =
[ Movie "1" "Se7en" 1995
, Movie "2" "Minority Report" 2002
, Movie "3" "The Godfather" 1972
]
getMovieHandler :: MovieId -> Handler (Maybe Movie)
getMovieHandler requestMovieId = go moviesDB
where
go [] = pure Nothing
go (movie:ms) | movieId movie == requestMovieId = pure $ Just movie
go (m:ms) = go ms
updateMovieHandler :: MovieId -> Movie -> Handler NoContent
updateMovieHandler requestedMovieId newMovie =
-- update the movie list in the database...
pure NoContent
deleteMovieHandler :: MovieId -> Handler NoContent
deleteMovieHandler _ =
-- delete the movie from the database...
pure NoContent
```
And assemble them together with the record structure, which is the glue here.
```haskell
2022-02-23 07:42:17 +01:00
server :: API AsServer
2022-02-21 11:39:37 +01:00
server =
API
{ version = versionHandler
, movies = moviesHandler
}
2022-02-23 07:42:17 +01:00
moviesHandler :: MoviesAPI AsServer
2022-02-21 11:39:37 +01:00
moviesHandler =
MoviesAPI
{ list = movieListHandler
, movie = movieHandler
}
2022-02-23 07:42:17 +01:00
movieHandler :: MovieId -> MovieAPI AsServer
2022-02-21 11:39:37 +01:00
movieHandler movieId = MovieAPI
{ get = getMovieHandler movieId
, update = updateMovieHandler movieId
, delete = deleteMovieHandler movieId
}
```
As you might have noticed, we build our handlers out of the same record types we used to define our API: `MoviesAPI` and `MovieAPI`. What kind of magic is this ?
Finally, we can run the server and connect the API routes to the handlers as usual:
``` haskell
api :: Proxy MovieCatalogAPI
api = Proxy
main :: IO ()
main = run 8081 app
app :: Application
app = serve api server
```
Yay! Thats done and weve got our server!
## The Client
The client, so to speak, is very easy to implement:
``` haskell
movieCatalogClient :: API (AsClientT ClientM)
2022-02-23 07:42:17 +01:00
movieCatalogClient = client api -- remember: api :: Proxy MovieCatalogAPI
2022-02-21 11:39:37 +01:00
```
Weve also introduced some operators that help navigate through the nested records.
`(//)` is used to jump from one record to another.
`(/:)` is used to provide a parameter, whether it be a query param or a capture.
Lets use those nice helpers for our movie catalog:
```haskell
listMovies :: Maybe SortBy -> ClientM [Movie]
listMovies sortBy = movieCatalogClient // movies // list /: sortBy
getMovie :: MovieId -> ClientM (Maybe Movie)
getMovie movieId = movieCatalogClient // movies // movie /: movieId // get
updateMovie :: MovieId -> Movie -> ClientM NoContent
updateMovie movieId newMovie = movieCatalogClient // movies // movie /: movieId // update /: newMovie
deleteMovie :: MovieId -> ClientM NoContent
deleteMovie movieId = movieCatalogClient // movies // movie /: movieId // delete
```
Done! Weve got our client!
## Conclusion
2022-02-23 07:42:17 +01:00
We hope that you found this cookbook helpful, and that you now feel more confident using the record-based APIs, nested or not.
2022-02-21 11:39:37 +01:00
If you are interested in further understanding the built-in Servant combinators, see [Structuring APIs](../structuring-apis/StructuringApis.html).
Since `NamedRoutes` is based on the Generic mechanism, you might want to have a look at [Sandy Maguires _Thinking with Types_ book](https://doku.pub/download/sandy-maguire-thinking-with-typesz-liborgpdf-4lo5ne7kdj0x).