Servant is a really nice library for building REST APIs in Haskell. However, it uses advanced GHC features which may not be familiar to some Haskell programmers. In this article, I explain type-level strings, type-level lists, type-level operators, and type families. Finally, I use code from servant-server to explain how these features are used in practice.
This article is aimed at people who have a basic familiarity with Haskell. This includes understanding things like typeclasses, applicatives, monads, monad transformers, pointfree style, ghci, etc.
This article will give you insight to how Servant is using these advanced Haskell features, and hopefully make you more productive when using Servant.
Servant Example
Here is a simple example of using servant-server. This code will be referred to throughout the article.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Main where
import Control.Monad.Trans.Either (EitherT)
import Network.Wai (Application)
import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.RequestLogger (logStdoutDev)
import Servant
( (:>), (:<|>)((:<|>)), Get, JSON, Proxy(..), ServantErr, ServerT, serve )
-- | A representation of our REST API at the type level.
--
-- This defines two routes:
-- * /dogs -- Responds to HTTP GET with a list of integers in JSON format.
-- * /cats -- Responds to HTTP GET with a list of Strings in JSON format.
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]
-- | A WAI 'Application' that will serve our API.
app :: Application
app = serve (Proxy :: Proxy MyAPI) myAPI
-- | Our entire API. You can see that it is a combination of the 'dogNums'
-- handler and the 'cats' handler.
myAPI :: ServerT MyAPI (EitherT ServantErr IO)
myAPI = dogNums :<|> cats
-- | A handler for the /dogs route. It just returns a list of the integers
-- one to four.
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]
-- | A handler for the /cats route.
cats :: EitherT ServantErr IO [String]
cats = return ["long-haired", "short-haired"]
-- | Run our 'app' as a WAI 'Application'.
main :: IO ()
main = run 32323 $ logStdoutDev appThe example project can be found on Github. The comments in the code should give a good idea as to what is going on, but if you would like a better introduction, the Servant tutorial is very good.
The following steps can be used to download and run the code. The stack build tool is used.
$ git clone [email protected]:cdepillabout/servant-example.git
$ cd servant-example
$ stack build
$ stack exec servant-notesThis runs a Warp server on port 32323. With the server running, curl can be used to test the API.
$ curl http://localhost:32323/dogs
[1,2,3,4]
$ curl http://localhost:32323/cats
["long-haired","short-haired"]
$The code can also be opened in ghci.
$ stack ghci
ghci> :load example.hs
ghci> :info app
app :: Application -- Defined at example.hs:17:1
ghci>The Motivation for Servant
Why does Servant exist? What is the main problem it solves?
Most web frameworks allow the user to write a handler for a specific route as a function. Here is an example of a handler function for a theoretical framework returning a JSON list [1,2,3,4]:
dogNums' :: SomeMonad Value
dogNums' = return $ toJSON [1,2,3,4]When a user makes a request to /dogs, this function would get called, and the framework would pass the generated JSON back to the user. The type of the handler function is SomeMonad Value. This means it is running in SomeMonad and returning a JSON Value.
This is not bad, but it’s not type safe. All the type signature says is that some kind of JSON is returned.
It would be nice to enforce that a list of Ints is returned. Ideally we would like to write this function like this:
dogNums'' :: SomeMonad [Int]
dogNums'' = return [1,2,3,4]The framework would be responsible for converting the list of Ints to JSON and returning it to the user.
Servant does this for us.
In our example, there are two handlers for two different routes. Here is the handler for the /dogs route:
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]How does dogNums relate to dogNums''?
SomeMonad would be EitherT ServantErr IO. The list of Ints is the same.
Servant is great because it gives us type safety in the return type of our handlers.
However, two important things are still missing. Servant needs to be told that the handler should be called when the user sends a GET request to /dogs. Servant also needs to be told to convert the Int list returned by the dogNums handler to JSON.
This information is encoded in the API type1:
type DogsAPI = "dogs" :> Get '[JSON] [Int]This type says that Servant will respond to GET requests to /dogs, returning a JSON-encoded list of Ints.
Before explaining how the dogNums function gets tied to the DogsAPI type, we first need to look at type-level strings, type-level lists, type-level operators, and type families.
Type-Level Strings
Recent versions of GHC support type-level strings. What’s a type-level string? Let’s play around with it in ghci.
First, the DataKinds language extension needs to be enabled.
ghci> :set -XDataKinds
ghci>Let’s try to get the kind of a type-level string:
ghci> :kind "hello"
"hello" :: GHC.TypeLits.Symbol
ghci>Hmm, the type-level string appears to be of kind GHC.TypeLits.Symbol. What can be done with this?
Looking at the GHC.TypeLits module, there appears to be a symbolVal function. It can be used to get back the value of the type-level string.
Let’s try this out in ghci. symbolVal and Data.Proxy.Proxy2 need to be imported. Proxy is used to “proxy” the type-level literal.
ghci> import GHC.TypeLits
ghci> import Data.Proxy
ghci> symbolVal (Proxy :: Proxy "hello")
"hello"
ghci>This is really cool! We are able to get back the concrete value of something that only exists on the type level!
How does Servant use this? Recall the MyAPI type defined near the top of this article:
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]"dogs" and "cats" are type-level strings. At the end of this article we will look at some servant-server code and confirm that it is using symbolVal to get the value of the type-level strings.
Type-Level Lists
Just like type-level strings, type-level lists can also be defined.
First, the DataKinds language extension needs to be enabled.
ghci> :set -XDataKinds
ghci>Let’s look at the kind of a type-level empty list:
ghci> :kind []
[] :: * -> *
ghci>No, wait, that’s not right. That’s just the kind of the normal list constructor. How do we write a type-level list?
Take quick peek at the GHC page on datatype promotion. The first section is pretty interesting, as is the section on the promoted list and tuple types. There is a short example of a heterogeneous list (or HList). A heterogeneous list is a list that has elements of different types. In the example, foo2 represents a heterogeneous list with two elements, Int and Bool.
From the example, you can see that type-level lists can be defined by putting a quote in front of the opening bracket:
ghci> :kind '[]
'[] :: [k]
ghci>Type-level lists can also be defined with multiple elements:
ghci> :kind '[Int, Bool, String]
'[Int, Bool, String] :: [*]
ghci>Going back to the MyAPI example from above, Servant is using type-level lists to represent the available content-type encodings of the response.
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]Servant is only willing to send back responses in JSON. (Because JSON is the only type in the type-level list).
Additional content types could also be specified:
type MyAPI = "dogs" :> Get '[JSON, FormUrlEncoded] [Int]
:<|> "cats" :> Get '[JSON, PlainText] Text(However, to get this to compile, there would need to be an instance of ToFormUrlEncoded [Int].) The /dogs route will then return either JSON or form-encoded values. The /cats route will return either JSON or plain text.
I’m not going to go into how type-level lists are used in servant-server, but if you’re interested you may want to start with reading the Get instance for HasServer, which will take you to the methodRouter function, which will take you to the AllCTRender typeclass. The AllCTRender typeclass/instance is where the real magic starts happening.
Oliver Charles has an interesting post on the generics-sop package where he talks a little about heterogeneous lists.
Type-Level Operators
In the Servant example code above, there are two type-level operators being used: (:>) and (:<|>). Type-level operators are similar to normal data types—they are just composed of symbols instead of letters.
Let’s look at how (:>) and (:<|>) are defined in Servant:
data path :> a
data a :<|> b = a :<|> bIf we didn’t want to write them infix, they could be written like this:
data (:>) path a
data (:<|>) a b = (:<|>) a bIn fact, if these data types were written with letters instead of symbols, they would look something like this:
data Foo path a
data Bar a b = Bar a bYou can see that (:>) and (:<|>) are just normal datatype definitions. They only look weird because they are made of symbols and written infix.
Type operators help when writing long type definitions. They keep the long type definition easy to understand. Take the following API definition:
type MyAPI = "foo" :> "bar" >: Get '[JSON] [Int]This defines the route /foo/bar. Rewriting this prefix would look like this:
type MyAPI = (:>) "foo" ((>:) "bar" (Get '[JSON] [Int]))You can see how much easier the infix style is to read!
NOTE: The TypeOperators language extension is needed to use the above code.
The GHC manual has a section about type-operators.
You may be thinking, “These type operators are pretty neat, but how are they actually used? They just look like confusing data types!” Well, we’ll get to that in a minute. Before we can jump into the Servant code, we need to get a basic understanding of type families.
Type Families
Type families are a relatively simple addition to Haskell that allow the user to do some computation at the type level. However, if you google for type families, it’s easy to get scared.
The first result is the GHC/Type families article on the Haskell Wiki. This is written with an advanced Haskeller in mind. Don’t worry if it’s too hard. (The other problem is that most of their examples use data families instead of type synonym families–which I introduce below. Most of the real world Haskell code I’ve seen uses type synonym families much more than data families).
The second link is to the type-families page in the GHC manual. It’s good if you already know about type families and just want a refresher, but it’s not good as an introduction to type families.
The third result is an article on FP Complete. It gets points for being about Pokemon, but the setup/motivation for using type families is way too long3.
The fourth result is an introduction to type families by Oliver Charles. It’s the best of the bunch, but it is slightly hard to follow if you’ve never used MVars, IORefs, etc.
I wrote a super simple tl;dr presentation about type families. Originally I wrote it in Japanese for a Haskell Lightning Talk in Tokyo, but I recently translated it to English upon the request from someone in the #haskell room in the functional programming slack community. If you aren’t sure about type families, please read that presentation and then proceed to the next section.
Servant
Now we come to the interesting section. How does Servant actually use type-level strings, type-level lists, type-operators, and type families? Let’s go back to the example code at the top of this blog post:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Main where
import Control.Monad.Trans.Either (EitherT)
import Network.Wai (Application)
import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.RequestLogger (logStdoutDev)
import Servant
( (:>), (:<|>)((:<|>)), Get, JSON, Proxy(..), ServantErr, ServerT, serve )
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]
app :: Application
app = serve (Proxy :: Proxy MyAPI) myAPI
myAPI :: ServerT MyAPI (EitherT ServantErr IO)
myAPI = dogNums :<|> cats
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]
cats :: EitherT ServantErr IO [String]
cats = return ["long-haired", "short-haired"]
main :: IO ()
main = run 32323 $ logStdoutDev appWe have the MyAPI type and the two handlers for the /dogs and /cats routes.
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]
cats :: EitherT ServantErr IO [String]
cats = return ["long-haired", "short-haired"]Our goal is to figure out how we get from the /dogs API type, to the actual handler type.
- API type
"dogs" :> Get '[JSON] [Int]- handler type
EitherT ServantErr IO [Int]
The following sections dive into actual code from servant-server’s master branch on Github. The code is currently between version 0.4.2 and 0.5.0.
Serve!
In the example code above, the two interesting functions are serve and myAPI. serve is provided by servant-server, while myAPI is written by us.
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]
app :: Application
app = serve (Proxy :: Proxy MyAPI) myAPI
myAPI :: ServerT MyAPI (EitherT ServantErr IO)
myAPI = dogNums :<|> catsLet’s look at the type of serve:
ghci> import Servant.Server
ghci> :type serve
serve :: HasServer layout => Proxy layout
-> Server layout
-> Network.Wai.ApplicationLet’s start with the easy things. It returns a Network.Wai.Application. This represents an application that can be served by Warp (i.e. something that can be passed to the run function provided by Warp).
The first argument is Proxy layout. The serve function uses this to figure out what the API type is. You might be asking, “If we are also passing the layout type variable to the Server type constructor, why do we additionally need to pass a Proxy layout? Surely, we don’t need to pass layout twice?”. That will be covered later.
Now look at the second argument, Server layout. What is Server?
ghci> :info Server
type Server layout = ServerT layout (EitherT ServantErr IO)Server looks like it is a specialization of ServerT around the EitherT monad transformer. This is similar to how the Reader monad is a specialization of the ReaderT monad4:
newtype ReaderT r m a = ...
type Reader r a = ReaderT r Identity aOkay, so Server is just a specialization of ServerT. Then what is ServerT?
ghci> :info ServerT
class HasServer (layout :: k) where
type family ServerT (layout :: k) (m :: * -> *) :: *
...This is what we’ve been waiting for! ServerT is a type family! It’s a function that computes a type. Let’s take a look at the HasServer typeclass before really diving into ServerT.
class HasServer layout where
type ServerT layout (m :: * -> *) :: *
route :: Proxy layout -> IO (RouteResult (ServerT layout (EitherT ServantErr IO))) -> RouterHasServer takes one type parameter, layout. ServerT is a type family that takes two parameters, layout and m.
There is one function in this typeclass, route. It takes a Proxy layout and an IO of a RouteResult of a ServerT with the m parameter specialized to EitherT ServantErr IO. Quite a mouthful. Let’s abbreviate part of the type to make it easier to digest:
route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> RouterBasically route takes an IO of a RouteResult of a ServerT and returns a Router. Let’s go back real quick and look at the implementation of the serve function:
serve :: HasServer layout => Proxy layout -> ServerT layout (EitherT ServantErr IO) -> Application
serve proxy server = toApplication (runRouter (route proxy (return (RR (Right server)))))The type of the serve function looks pretty similar to the route function:
serve :: HasServer layout => Proxy layout -> (ServerT layout ...) -> Application
route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> RouterSo how does the serve function work? It’s basically taking our myAPI (the server argument below) argument, wrapping it in a RouteResult and IO, then passing it to the route function.
serve :: HasServer layout => Proxy layout -> (ServerT layout ...) -> Application
serve proxy server = toApplication (runRouter (route proxy (return (RR (Right server)))))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
look at all this wrapping!!!It takes the resulting Router from the route function, passes it to runRouter, and then passes that to toApplication to get the Wai application. Pretty easy! Let’s see it point free!
serve :: HasServer layout => Proxy layout -> (ServerT layout ...) -> Application
serve proxy = toApplication . runRouter . route proxy . return . RR . Right
^^^^^^^^^^^^^^^^^^^
look at this pointfree wrapping!!!Understanding serve isn’t strictly necessary to understanding the rest of this article, but it is interesting.
Our Progress so far
Here’s what we’ve learned so far, in convenient bullet-point form:
We have a
MyAPItype, and we want to figure out how that gets translated to thedogNumsandcatshandler.type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] dogNums :: EitherT ServantErr IO [Int] dogNums = return [1,2,3,4] cats :: EitherT ServantErr IO [String] cats = return ["long-haired", "short-haired"]It looks like the translation is basically happening in the Servant-provided
servefunction:type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] app :: Application app = serve (Proxy :: Proxy MyAPI) myAPI myAPI :: ServerT MyAPI (EitherT ServantErr IO) myAPI = dogNums :<|> catsThe
servefunction is basically just callingroute.serve :: HasServer layout => Proxy layout -> (ServerT layout ...) -> Application serve proxy = toApplication . runRouter . route proxy . return . RR . RightThe
routefunction is defined in theHasServertypeclass.class HasServer layout where type ServerT layout (m :: * -> *) :: * route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> Router
The next section will look at how the HasServer typeclass and route function interact to convert "dogs" :> Get '[JSON] [Int] to EitherT ServantErr IO [Int].
HasServer, one more time
Let’s go back to the HasServer typeclass. Here it is again:
class HasServer layout where
type ServerT layout (m :: * -> *) :: *
route :: Proxy layout -> IO (RouteResult (ServerT layout (EitherT ServantErr IO))) -> RouterThis typeclass specifies things that can be used to create a Router. A Router can then be turned into a Wai application.
So what instances are available for the HasServer typeclass? Let’s ask ghci.
ghci> :info! HasServer
...
instance AllCTRender ctypes a => HasServer (Get ctypes a)
...
instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout)
instance (HasServer a, HasServer b) => HasServer (a :<|> b)
ghci>:info! shows us all the instances defined for a typeclass. Look at the difference between :info HasServer and :info! HasServer.
There are instances defined for Get, (:>), (:<|>). I know where we’ve seen those before! The MyAPI type!
Let’s take a look at the MyAPI type defined earlier in the example code:
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]Remember how type-level operators can be rewritten to prefix form? Rewriting (:<|>) to prefix form becomes this:
type MyAPI = (:<|>) ("dogs" :> Get '[JSON] [Int]) ("cats" :> Get '[JSON] [String])The inner (:>) could also be rewritten to prefix form and it will get even uglier:
type MyAPI = (:<|>) ((:>) "dogs" (Get '[JSON] [Int])) ((:>) "cats" (Get '[JSON] [String]))Okay, so here’s where the explanation starts to get a little difficult. Remember the app function?
app :: Application
app = serve (Proxy :: Proxy MyAPI) myAPI
myAPI :: ServerT MyAPI (EitherT ServantErr IO)
myAPI = dogNums :<|> cats
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]
cats :: EitherT ServantErr IO [Int]
cats = return ["long-haired", "short-haired"]It’s just calling serve and passing it two things:
a
Proxywith theMyAPItype.the
myAPIfunction, which is the actual implementation of the API.
You remember what serve does, right?
serve :: HasServer layout => Proxy layout -> ServerT layout (EitherT ServantErr IO) -> Application
serve proxy server = toApplication (runRouter (route proxy (return (RR (Right server)))))It basically calls route with the proxy and the implementation of the API.
Now for the interesting part. Since HasServer is a typeclass, what route function actually gets called? If we look at the HasServer typeclass once again, we can see that the specific route function that gets called depends on the type of layout (which gets passed to route as Proxy layout).
class HasServer layout where
type ServerT layout (m :: * -> *) :: *
route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> Routerlayout originally comes from the app function in the example code.
app :: Application
app = serve (Proxy :: Proxy MyAPI) myAPIHere it’s MyAPI. What’s the prefix form of MyAPI?
type MyAPI = (:<|>) ((:>) "dogs" (Get '[JSON] [Int])) ((:>) "cats" (Get '[JSON] [String]))Okay, great! So it looks like the HasServer instance for (:<|>) can be used! What does it look like?
instance (HasServer a, HasServer b) => HasServer (a :<|> b) where
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m
route :: Proxy (a :<|> b)
-> IO (RouteResult ( ServerT a (EitherT ServantErr IO)
:<|> ServerT b (Eithert ServantErr IO)
)
)
-> Router
route Proxy server = choice (route pa (extractL <$> server))
(route pb (extractR <$> server))
where pa = Proxy :: Proxy a
pb = Proxy :: Proxy bWhat’s going on here? The first thing to notice is that the value of the ServerT (a :<|> b) m type family becomes ServerT a m :<|> ServerT b m:
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b mWhat’s the significance of this? Two things. One, the new, specialized type of route can be deduced:
route :: Proxy layout -> IO (RouteResult (ServerT layout ...) ) -> Router
-- becomes
route :: Proxy (a :<|> b) -> IO (RouteResult (ServerT a ... :<|> ServerT b ...)) -> RouterAnd two, the type of the myAPI function from the example program can be changed to this specialized type, and the example program will still compile. Before, it looked like this:
myAPI :: ServerT MyAPI (EitherT ServantErr IO)
myAPI = dogNums :<|> catsBut it could be changed to this5:
myAPI :: ServerT ("dogs" :> Get '[JSON] [Int]) (EitherT ServantErr IO)
:<|> ServerT ("cats" :> Get '[JSON] [String]) (EitherT ServantErr IO)
myAPI = dogNums :<|> catsIt still compiles! That’s great!
One Level Deeper
Going back to the HasServer instance for (:<|>), we see that the route function calls itself recursively on both arguments to (:<|>). For these recursive calls, which route function will be called?
instance (HasServer a, HasServer b) => HasServer (a :<|> b) where
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m
route :: Proxy (a :<|> b)
-> IO (RouteResult ( ServerT a (EitherT ServantErr IO)
:<|> ServerT b (Eithert ServantErr IO)
)
)
-> Router
route Proxy server = choice (route pa (extractL <$> server))
(route pb (extractR <$> server))
where pa = Proxy :: Proxy a
pb = Proxy :: Proxy bRecall our MyAPI type:
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]The first argument to (:<|>) is the following:
"dogs" :> Get '[JSON] [Int]Written infix it looks like this:
(:>) "dogs" (Get '[JSON] [Int])You can probably see where this is going. In the recursive calls to route, the route function for the (:>) instance of HasServer will be called.
Here is the HasServer instance for (:>):
instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where
type ServerT (path :> sublayout) m = ServerT sublayout m
route :: Proxy (path :> sublayout)
-> IO (RouteResult (ServerT sublayout (EitherT ServantErr IO)))
-> Router
route Proxy subserver = StaticRouter $
M.singleton (symbolVal proxyPath)
(route (Proxy :: Proxy sublayout) subserver)
where proxyPath = Proxy :: Proxy pathThe value of the ServerT (path >: sublayout) type family becomes ServerT sublayout m. The path argument is not used.
Here is the specialized type of the route function:
route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> Router
-- becomes
route :: Proxy (path :> sublayout) -> IO (RouteResult (ServerT sublayout ...)) -> RouterJust like above, the type of myAPI can be changed to match this. After the last change, it looked like this:
myAPI :: ServerT ("dogs" :> Get '[JSON] [Int]) (EitherT ServantErr IO)
:<|> ServerT ("cats" :> Get '[JSON] [String]) (EitherT ServantErr IO)
myAPI = dogNums :<|> catsBecause the path argument is ignored, it can be changed to this:
myAPI :: ServerT (Get '[JSON] [Int]) (EitherT ServantErr IO)
:<|> ServerT (Get '[JSON] [String]) (EitherT ServantErr IO)
myAPI = dogNums :<|> catsStill compiles! Great!
If the path argument in ServerT (path :> sublayout) is ignored in the value of the type family, what is it actually used for?
symbolVal is used to get the value of the path type! It’s using the value of path to do the routing. It’s creating a Map that can later be used to lookup the path piece.
route :: Proxy (path :> sublayout)
-> IO (RouteResult (ServerT sublayout (EitherT ServantErr IO)))
-> Router
route Proxy subserver = StaticRouter $
Map.singleton (symbolVal proxyPath)
(route (Proxy :: Proxy sublayout) subserver)
where proxyPath = Proxy :: Proxy pathroute is then called recursively on subsever, which has type sublayout.
In the example code, subserver will be the dogNums function, and the sublayout type will be Get '[JSON] [Int].
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]Our Progress so far #2
Here’s an update on what we’ve learned so far:
We have a
MyAPItype, and we want to figure out how that gets translated to thedogNumsandcatshandler.type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] dogNums :: EitherT ServantErr IO [Int] dogNums = return [1,2,3,4] cats :: EitherT ServantErr IO [String] cats = return ["long-haired", "short-haired"]It looks like the translation is basically happening in the Servant-provided
servefunction:type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] app :: Application app = serve (Proxy :: Proxy MyAPI) myAPI myAPI :: ServerT MyAPI (EitherT ServantErr IO) myAPI = dogNums :<|> catsThe
servefunction is basically just callingroute.serve :: HasServer layout => Proxy layout -> (ServerT layout ...) -> Application serve proxy = toApplication . runRouter . route proxy . return . RR . RightThe
routefunction is defined in theHasServertypeclass.class HasServer layout where type ServerT layout (m :: * -> *) :: * route :: Proxy layout -> IO (RouteResult (ServerT layout ...)) -> RouterWhen
routeis passed the top-levelMyAPItype, theroutefunction in theHasServerinstance for(:<|>)is called.instance (HasServer a, HasServer b) => HasServer (a :<|> b) where type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m route :: Proxy (a :<|> b) -> IO (RouteResult ( ServerT a ... :<|> ServerT b ... )) -> Router route Proxy server = choice (route pa (extractL <$> server)) (route pb (extractR <$> server)) where pa = Proxy :: Proxy a pb = Proxy :: Proxy bThe type of the
myAPIfunction can be changed to match the value of theServerTtype family:myAPI :: ServerT MyAPI (EitherT ...) -- becomes myAPI :: ServerT ("dogs" :> Get ...) (EitherT ...) :<|> ServerT ("cats" :> Get ...) (EitherT ...)In the
HasServerinstance for(:<|>),routeis called recursively with the type"dogs" :> Get '[JSON] [Int]. The correspondingroutefunction is defined in theHasServerinstance for(:>).instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where type ServerT (path :> sublayout) m = ServerT sublayout m route :: Proxy (path :> sublayout) -> IO (RouteResult (ServerT sublayout ...)) -> Router route Proxy subserver = StaticRouter $ M.singleton (symbolVal proxyPath) (route (Proxy :: Proxy sublayout) subserver) where proxyPath = Proxy :: Proxy pathThis basically throws away the path argument, and does a similar transformation to above:
ServerT ("dogs" :> Get ...) (EitherT ...) -- becomes ServerT (Get ...) (EitherT ...)
We’re very close to figuring out how Servant is able to go from the MyAPI type "dogs" :> Get '[JSON] [Int] to the type of our handler EitherT ServantErr IO [Int].
In the next section we will look at the last part of the puzzle, the Get instance of HasServer.
Red Pill, Blue Pill, Bottom of the Rabbit Hole
Here is the Get instance of HasServer:
instance ( AllCTRender contentTypes a ) => HasServer (Get contentTypes a) where
type ServerT (Get contentTypes a) m = m a
route :: Proxy (Get contentTypes a)
-> IO (RouteResult (m a))
-> Router
route Proxy = methodRouter methodGet (Proxy :: Proxy contentTypes) ok200Here is the specialized type of the route function:
route :: Proxy layout -> IO (RouteResult (ServerT layout m)) -> Router
-- becomes
route :: Proxy (Get contentTypes a) -> IO (RouteResult (m a)) -> RouterIn this instance, the ServerT (Get contentTypes a) m type family simply becomes m a.
In our case,
misEitherT ServantErr IOais[Int]
ServerT (Get contentTypes a) m becomes EitherT ServantErr IO [Int].
That’s why the type of dogNums is EitherT ServantErr IO [Int].
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]Just like above, the type of myAPI can be rewritten and it will still compile:
myAPI :: EitherT ServantErr IO [Int]
:<|> EitherT ServantErr IO [String]
myAPI = dogNums :<|> catsWe won’t go into how the route function is implemented here, but if you are interested, you’re welcome to look at the implementation of methodRouter. methodRouter does the actual rendering of the return type. For example, it will turn our [Int] into a JSON blob.
Because methodRouter handles the rendering of the return type, route needs to pass it Proxy contentTypes so that methodRouter knows what type to render.
Wrap-Up
At a very high-level, the HasServer typeclass, ServerT type family, and route function are used to peel away levels of the MyAPI type:
type MyAPI = "dogs" :> Get '[JSON] [Int]
:<|> "cats" :> Get '[JSON] [String]First, (:<|>) is peeled away leaving us with "dogs" :> Get '[JSON] [Int]. Then (:>) is peeled away leaving us with Get '[JSON] [Int]. This gets turned into the actual type of dogNums: EitherT ServantErr IO [Int].
dogNums :: EitherT ServantErr IO [Int]
dogNums = return [1,2,3,4]Why Pass layout Twice?
In the beginning of the Serve! section, a question was asked about the route function and the HasServer typeclass.
class HasServer layout where
type ServerT layout (m :: * -> *) :: *
route :: Proxy layout
-> IO (RouteResult (ServerT layout ...))
-> RouterHere is the question that was asked:
In the
routefunction, if we are passing thelayouttype variable to theServerTtype constructor, why do we additionally need to pass aProxy layout? Surely, we don’t need to passlayouttwice?
This question was recently answered on Stack Overflow by Alp Mestanogullari (one of the developers of servant).
He says that the main reason we need to pass layout twice is that type families, like ServerT, are not injective. An explanation of injectivity is given on the Haskell Wiki page on type families.
If we have ServerT a m and ServerT b m, even if we know that ServerT a m == ServerT b m and m == m, we cannot conclude that a == b. (This is in contrast to a type like Maybe a and Maybe b, where if we know that Maybe a == Maybe b, then we also know that a == b.)
The route function effectively doesn’t get to “see” the layout passed to ServerT. It only “sees” the type that ServerT turns into.
For example, take these two imaginary instance of HasServer:
instance HasServer (Lala a) where
type ServerT (Lala a) = a
route :: Proxy (Lala a)
-> IO (RouteResult a)
-> Router
instance HasServer (Popo a) where
type ServerT (Popo a) = a
route :: Proxy (Popo a)
-> IO (RouteResult a)
-> RouterIf route wasn’t passed a Proxy as the first argument, its type signature would look like this:
route :: IO (RouteResult (ServerT ...) -> RouterLet’s see what it would look like for the HasServer (Lala a) instance:
route :: IO (RouteResult (ServerT (Lala a)) -> RouterHowever, the type family tells us that ServerT (Lala a) = a, so this type signature becomes:
route :: IO (RouteResult a) -> RouterWe can look at the same thing for the HasServer (Popo a) instance:
route :: IO (RouteResult (ServerT (Popo a)) -> Router
-- because we know that @ServerT (Popo a) = a@, we can figure out that the type
-- signature of 'route' becomes:
route :: IO (RouteResult a) -> RouterThe resulting type signature for both instances is the same. Servant gets around this problem by passing a Proxy specifying the type we want to use.
In servant-server, a problem like this comes up with the HasServer instance for (:>).
instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where
type ServerT (path :> sublayout) m = ServerT sublayout m
route :: Proxy (path :> sublayout)
-> IO (RouteResult (ServerT sublayout ...))
-> RouterThe ServerT type family completely ignores the path argument! In the implementation of the route function, if we didn’t have the Proxy (path :> sublayout) argument, we wouldn’t be able to use the path argument at all!6
Conclusion
If you liked this tutorial, you may also like the official servant tutorial, or a tutorial about using servant with persistent by Matt Parsons.
Thanks
After completing a rough draft of this blog post, I emailed all three main servant developers (Julian K. Arni, Alp Mestanogullari, and Sönke Hahn) asking them if they would review it. Since it’s such a long blog post, and I’m sure they are busy guys, I was expecting maybe one of them to respond, but to my surprise, all three responded within hours of sending the email. They all took the time not only to read through this post, but to give very helpful feedback.
If any of you ever come to Tokyo, dinner is on me!
Footnotes
Technically, this information is partially found in the API type, and partially comes from the fact that you arrange your
Serverhandlers in the same order as the corresponding endpoints in the API type.Later parts of the article will talk more about this in depth, but you can get an idea for what it means by looking at the
myAPIfunction.type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] app :: Application app = serve (Proxy :: Proxy MyAPI) myAPI myAPI :: ServerT MyAPI (EitherT ServantErr IO) myAPI = dogNums :<|> cats dogNums :: EitherT ServantErr IO [Int] dogNums = return [1,2,3,4] cats :: EitherT ServantErr IO [String] cats = return ["long-haired", "short-haired"]servant requires you to write the handlers for your endpoints in the same order that the corresponding endpoints appear in the API type. It is by relying on this order that servant can cross-reference the information found in the API types and the types of the handlers themselves, in order to check that you’re not returning an
Intwhere aStringis expected.For example, based on the order of the “/dogs” and “/cats” handler in the
MyAPItype, GHC would throw an error if you revered the order ofdogsNumsandcatsin themyAPIfunction.type MyAPI = "dogs" :> Get '[JSON] [Int] :<|> "cats" :> Get '[JSON] [String] -- This works. myAPI :: ServerT MyAPI (EitherT ServantErr IO) myAPI = dogNums :<|> cats -- This does not compile. myAPI :: ServerT MyAPI (EitherT ServantErr IO) myAPI = cats :<|> dogNumsThis information will be clarified later in the article.↩
If you’ve never seen
Data.Proxy.Proxybefore, it is normally used to pass type information to a function. For instance, imagine the following function:read :: Read a => String -> a read = ... show :: Show a => a -> String show = ... badFunc :: String -> String badFunc string = show $ read stringWhen trying to compile
badFunc, GHC will throw an error.readandshoware polymorphic, so GHC can’t figure out what the type variableashould be.If we knew at compile time that we wanted it to be, say, an
Int, the function could be written like this:okayFunc :: String -> String okayFunc string = (show :: Int -> String) $ read stringWe’ve specialized the
showfunction to take anInt. GHC will be able to infer thatreadneeds to return anInt.ghci> okayFunc "3" "3" ghci> okayFunc "True" *** Exception: Prelude.read: no parse ghci>This works, but there is still one problem left. What if we want the caller to be able to determine the type? Like we tried to do in
ghciabove, what if we want to be able to parseBools as well asInts? We can useProxyto do this.goodFunc :: forall a. (Read a, Show a) => Proxy a -> String -> String goodFunc _ string = (show :: a -> String) $ read stringNote: For this example we need to enable the
ScopedTypeVariableslanguage pragma.We specify that
show’s type signature isa -> String. Thisais being passed in asProxy a.In
ghci,goodFunccan be used like this:↩ghci> goodFunc (Proxy :: Proxy Int) "3" "3" ghci> goodFunc (Proxy :: Proxy Bool) "True" "True" ghci> goodFunc (Proxy :: Proxy Integer) "lalala" *** Exception: Prelude.read: no parseThis article is also super long, so I really shouldn’t complain about length.↩
The article A Gentle Introduction to Monad Transformers might be a good place to start if you’re not too familiar with Monad transformers. However, if you’re not too familiar with Monad transformers, the rest of this article will probably be quite challenging.↩
It may be easier to reason about this code using convenient type synonyms. Originally we had this:
myAPI :: ServerT ("dogs" :> Get '[JSON] [Int]) (EitherT ...) :<|> ServerT ("cats" :> Get '[JSON] [String]) (EitherT ...) myAPI = dogNums :<|> catsBut it may be be easier to think about it like this:
↩type DogsAPI = "dogs" :> Get '[JSON] [Int] type CatsAPI = "cats" :> Get '[JSON] [String] myAPI :: ServerT DogsAPI (EitherT ...) :<|> ServerT CatsAPI (EitherT ...) myAPI = dogNums :<|> catsIn fact, even if we didn’t use
path, we would still have to use aProxy. This is because the arguments to a type family declared inside a typeclass need to be used in a way that makes them unambiguous in functions making use of that type family.It’s awkward to explain, but it is pretty easy to understand when you see an example.
In the following typeclass, there is one type family and two functions using that type family:
class Baz a where type Hoge a myGoodFunc :: a -> Hoge a -> Char myBadFunc :: Hoge a -> CharNow imagine we had the following two instances:
instance Baz String where type Hoge String = Int myGoodFunc :: String -> Int -> Char myGoodFunc = ... myBadFunc :: Int -> Char myBadFunc = ... instance Baz Text where type Hoge Text = Int myGoodFunc :: Text -> Int -> Char myGoodFunc = ... myBadFunc :: Int -> Char myBadFunc = ...We use
myGoodFuncandmyBadFunclike below:exampleGood :: String -> Int -> Char exampleGood string int = myGoodFunc string int exampleBad :: Int -> Char exampleBad int = myBadFunc intIn
exampleGood, GHC knows to pick themyGoodFuncfrom theBaz Stringinstance because the first argument tomyGoodFuncis aString.However, in
exampleBad, GHC doesn’t know whichmyBadFuncto pick. Should it pickmyBadFuncfrom theBaz Textinstance, or from theBaz Stringinstance? It doesn’t have enough information to decide. GHC will throw a compilation error.The
Baztypeclass could be rewritten to makemyBadFuncunambiguous.class Baz a where type Hoge a myGoodFunc :: a -> Hoge a -> Char myBadFunc :: Proxy a -> Hoge a -> Char instance Baz String where type Hoge String = Int myGoodFunc :: String -> Int -> Char myGoodFunc = ... myBadFunc :: Proxy String -> Int -> Char myBadFunc = ... instance Baz Text where type Hoge Text = Int myGoodFunc :: Text -> Int -> Char myGoodFunc = ... myBadFunc :: Proxy Text -> Int -> Char myBadFunc = ...exmapleBadwould also have to be rewritten:exampleBad :: Int -> Char exampleBad int = myBadFunc int -- becomes exampleBad :: Int -> Char exampleBad int = myBadFunc (Proxy :: Proxy String) intNow GHC knows to call
myBadFuncfrom theBaz Stringinstance.The
HasServertypeclass is also using thisProxytrick. That is why passing aProxyis necessary.The key takeaway is: when you know something like
Maybe a, you knowa. when you knowHoge a, you don’t knowa. In the two typeclass instances above,Hoge StringandHoge TextbecomeInt, so if all you have isInt, GHC doesn’t know whether you started withHoge StringorHoge Text. GHC can’t pick the right typeclass instance.↩