Diving into Servant
20 minutes reading timeOverview
We will explore how Servant achieves its type safe REST server definition. To accomplish this, it needs to solve two different challenges. First of all it has to deduce the types of the functions that will implement our server api. Secondly, it has to make sure it calls the correct function while handling a request.
As often discussed, it leverages Data Kinds for this, but that is not the most important mechanism. Servant’s main course is type families. In this blog post, we will show how, by applying type families recursively over the API type, it successfully tackles both challenges. We will trade the DataKinds extension for more boiler plate. It should also make it easier to see what is going on behind the scenes.
Type families
We will not make this a primer about type families. There’s a rather good if somewhat dry explanation here. There’s a longer but spicier explanation to be found here, for the pokemon fans. For the purpose of this blog, type families can basically be interpreted as mapping from one type, to a set of functions and other types. This is conceptually an extension of the more common type classes, which map from one type, to -only- a set of functions.
Routing
Servant has a small internal framework that concerns itself with routing requests. We will not go too deep into it, only touch upon it when we need it. The code can be found in the servant-server package. Important parts are the RoutingApplication and the RouteResult. The RouteResult is basically an Either type with two types of failure, Fail (fail-but-continue) and FailFatal (fail-hard-and-don’t-continue).
The flow of the routing package is straightforward, a request will be handed to an implementing function. If that function returns a Fail, the next function will be tried. If it succeeds, the request is handled. If there is no next function or it gets a FailFatal along the line, the request has failed.
You can see it has a strong feeling of firewall rule handling to it.
Servant’s Internals
We’ll try to show how Servant does its thing internally by, instead of using Servant types (such as Capture or the “comments” String), defining types ourselves and give those the same meaning as the Servant types by providing a correct instance for the type classes/type family.
HasServer is Servant’s type family for creating servers, we will delve into it in the rest of the post.
We’ll use the example we explored in the previous blog posts as well, a REST API for comments, containing one REST resource, comments, and a GET and POST on that REST resource. THat simple API will be enough to explore Servant’s internals. We’ll start off with the “comments” String. The DataKinds extension will give this the KnownSymbol type. If you want to see the generic instance of HasServer for KnownSymbol you can find that in the Servant library. We, however, will not rely on the KnownSymbol instance and will provide our own, but we will remove as much of the genericity as possible, for clarity.
Our own Comments type and its HasServer implementation
We start by defining a type Comments
and use it in an API. You can see the API is a bit oversimplified currently.
data Comments = Comments
type ExplainApi = Comments :> Get '[JSON] String
getComment :: Handler String
getComment = return "I comment!"
server :: Server ExplainApi
server = getComment
serveExplainApi :: Int -> IO ()
serveExplainApi port = run port $ serve explainApi server
Let’s look a little closer at the HasServer type family and start providing an instance for our Comments
type.
class HasServer api context where
type ServerT api (m :: * -> *) :: *
route ::
Proxy api
-> Context context
-> Delayed env (Server api)
-> Router env
hoistServerWithContext
:: Proxy api
-> Proxy context
-> (forall x. m x -> n x)
-> ServerT api m
-> ServerT api n
type Server api = ServerT api Handler
It consists of an associated type ServerT
, and two functions, route
and hoistServerWithContext
. Every instance we show here will as such need a type, an implementation for route
and an implementation for hoistServerWithContext
.
Let’s leave the two functions alone for now and check how we can define the associated type for Comments
.
What we want to achieve here is that we can use our Comments
type instead of the “comments” String.
The associated type
In REST terms, Comments
is a resource. The resource does not really play any kind of role in the type of a function that implements the goings-on on the resource. It is only important in the routing, so the associated data type is rather straightforward, we will peel of the Comments
layer of the type without using it here (we will however use it a later when we implement the route
function, it’s not a useless part of the type after all):
instance HasServer api context => HasServer (Comments :> api) context where
type ServerT (Comments :> api) m = ServerT api m
Note the recursiveness here of the HasServer instance. The api
type in our case will be Get '[JSON] String
.
Normally we would use the serve
function to serve an api type.
Due to this serve
function using the Server
type and the Server
type being explicitly defined as
type Server api = ServerT api Handler
we can conclude that the HasServer
implementation of this type will have as associated type Handler String
, at the end, when everything has been handled. This explains where the Handler
monad in our getComment
function type (being Handler String
) comes from.
Next up, the functions : route
and hoistServerWithContext
.
The route function
Let’s start with route
and leverage the pathRouter functionality from the Router package like we said. This pathRouter will make sure our function is only invoked when the REST resource in the HTTP request is “comments”. If not, it will return RouteResult.Fail
(recall the fail-but-continue failure type used in the routing sub-library).
route Proxy context subServer =
pathRouter
"comments"
(route (Proxy :: Proxy api) context subServer)
You can see that this is a recursive function, we are handling an api of type Comments :> api
, on which we match by using Proxy
. We consume the Comments
part (create our router) and recursively call the route function of api
which will then apply its specifics.
This recursive peeling will continue until we hit the last part of our API, which is always one of the HTTP verbs.
The hoistServerWithContext function
The last part we need to tackle for a complete HasServer
definition is the hoistServerWithContext
function.
Recall that we used hoistServer
to have the functions implementing our server run in a different monad than the Handler
monad. The function takes a transformer function, from our favourite monad to the Handler
monad and has to be applied at the end of the chain.
The hoistServerWithContext
, the more general version of hoistServer
also takes a context. A context is a bit nebulous as a concept, but the explanation in the servant library tells us we have to see it as typed key-value pairs, a heterogenous list. We will not really need it in our implementation so we will just pass it down.
Our implementation then becomes :
hoistServerWithContext (Proxy :: Proxy (Comments :> api)) proxyContext transformer servantApi =
hoistServerWithContext (Proxy :: Proxy api) proxyContext transformer servantApi
We basically descend into the api type, where at the end the transformer will be applied. The transformer from our earlier blogs is runReaderT
, as an example.
Alright, now we have our full HasServer instance.
Servant’s mechanics can be thought of as : the user provides an onion-like type, where every part provides an instance of the HasServer
type family.
The associated type and the functions of every part are implemented in a recursive way, each descending through all the layers until you reach the core, the core being one of the HTTP verbs.
Along the way a type representing the functions necessary for serving the api emerges, as well as a routing function.
We achieve all of this without the magical DataKinds extension as well, but you can see we cheat a bit by making it a lot easier on ourselves, assuming a very specific API and coding everything to serve just that API.
End of the line : the HasServer Verb implementation
As mentioned above, the end of the line of the API type we provide is always an HTTP Verb. The HasServer instance for the HTTP verb looks like this:
instance {-# OVERLAPPABLE #-}
( AllCTRender ctypes a, ReflectMethod method, KnownNat status
) => HasServer (Verb method status ctypes a) context where
type ServerT (Verb method status ctypes a) m = m a
hoistServerWithContext _ _ nt s = nt s
So basically, ServerT does not descend any further, it becomes the default Handler
monad (unless we want to run in a different monad of course), which is why our getComment
function needs to have the type Handler String
.
The hoistServerWithContext
function does not bother with anything except the transformer (called nt
here), and it applies it to the server api. This is how our functions can run in our specialized AppM
monad in the earlier blog.
Let’s go for something a little more complicated now, let’s try to capture a type.
The HasServer implementation for Capture
Let’s say we want to make a type that will just capture a comment id and nothing else.
data CaptureCommentId = CaptureCommentId
We wil redefine our api to use this Capture type
type ExplainApi = Comments :> CaptureCommentId :> Get '[JSON] String
We will also change the getComment
type to resemble something useful, the type we expect from Servant :
getComment :: Int -> Handler String
getComment id = return $ "pretend this is comment number " ++ show id
The associated type
Okay, now providing our HasServer instance, we first have to decide what the associated type will be. This means deciding what we want the type of the capture to be when encountering a CaptureCommentId
. We decide here that this will always be an Int, but if you want to make it more generic (as Servant does) you depend on the DataKinds and the type lists that you can see in all examples. We, in our simple implementation, have none of this complexity of course.
instance (HasServer api context) => HasServer (CaptureCommentId :> api) context where
type ServerT (CaptureCommentId :> api) m = Int -> ServerT api m
This implementation tells us that as soon as we encounter a CaptureCommentId :> api
we associate a function Int -> ServerT api m
with it. You can see again how the definition descends through the type like this until it ends up at one of the verbs. The verb implementation does not recurse anymore, as we showed above.
The hoistServerWithContext function
Now for something a little more complicated, the hoistServerWithContext
implementation. Recall that this function’s reason of existence is allowing us to use a different monad than the Handler
monad and it evolves around the transformer function we have to supply. We did not go too deep into it for the Comments
type but we will have to delve a little deeper here.
Recall that the goal of this function, in case we do run in a different monad than Handler, is to allow us to write our getComment
function in another monad, like this :
getComment :: Int -> MyFavouriteMonad String
getComment id = return $ "pretend this is comment number " ++ show id
We have to provide a function that will translate MyFavouriteMonad
to Handler
, a function with type MyFavouriteMonad -> Handler
basically.
Internally, Servant wants to run in Handler but still allow you to provide your own monad for your specific needs. How can we achieve that with the hoistServerWithContext
function, whose signature looks like this?
hoistServerWithContext :: Proxy api -> Proxy context -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n
Note that the m
monad here is our MyFavouriteMonad and the n
monad is the Handler monad. The end result needs to be that we can pass a function Int -> MyFavouriteMonad String
to that hoistServerWithContext
and it knows what to do with it.
We can achieve that goal like this. It’s written a bit more lengthy so we can explain the in-between types that we use. Bear in mind that we need to use the full api type and so we need to move on the next layer of the typing.
As such we need to try to call the hoistServerWithContext
function for api
from within the hoistServerWithContext
function of CaptureCommentId :> api
.
hoistServerWithContext (Proxy :: Proxy (CaptureCommentId :> api)) proxyContext transformer server =
let curried = hoistServerWithContext (Proxy :: Proxy api) proxyContext transformer in let result = curried . server in result
Let’s start by investigating server
.
The server
parameter is of type ServerT (CaptureCommentId :> api) m
, with m
our MyFavouriteMonad
. Recall that we defined this type, the associated type of this instance, to be equvalent to Int -> ServerT api m
. Descending into the types would make this eventually Int -> MyFavouriteMonad String
.
Combining the definition of hoistServerWithContext
with the partial application we see here, we know that the curried
variable is of type ServerT api m -> ServerT api n
or for our specific monads, MyFavouriteMonad a -> Handler a
.
It then stands to reason that function composition of server
and curried
will give us the function Int -> Handler String
, if we supply it with a server implementation Int -> MyFavouriteMonad String
, which, recall is our goal. We want to run our get
function in the MyFavouriteMonad
monad.
The route function
Okay, hoistServerWithContext
nailed down, what about route
? To summarize, route
needs to check whether there is a part of the REST resource trailing after the comments
sub resource and needs to parse that as an Int. It needs to dispatch that Int to our implementing function.
Like we mentioned at the beginning of the article, we will not try to rewrite the routing-miniframework inside Servant, we will just use it. Looking at that framework it means we have to leverage the CaptureRouter
constructor.
We know that the type variable a
in that constructor will be of the RoutingApplication
type (because of the standard Router
type), so we need to get something of the type (Router' (Text, env) RoutingApplication)
and pass that to the CaptureRouter
constructor. We will use another part of the routing framework, namely addCapture to achieve this.
The route
function will take this form in our case:
route Proxy context subServer = let readFun = return . read . cs in let capt = addCapture subServer readFun in CaptureRouter $ route (Proxy :: Proxy api) context capt
Let’s start with noting that the type of subServer
is Delayed env (Server (CaptureCommentId :> api) )
with Server
shorthand for ServerT api Handler
. We don’t need to worry about different monads here, that is done in the hoistServerWithContext
function.
Delayed
is describere here, mainly a bag of functions running in the DelayedIO
monad.
That monad is an IO monad embellished with the RouteResult
type, so it can fail softly.
The subServer
fits nicely into the first slot in our addCapture
function, which only needs a function to translate Text
to Int
, inside the DelayedIO
monad. The readFun
we assembled here has type Text -> DelayedIO Int
, so that’s our guy!
capt
is our Delayed (Text, env) (ServerT api Handler)
which fits nicely into the CaptureRouter
type, as it wants a Router (Text, env)
. Of course, we can easily use the read
function cause we know we want an Int for our specific CaptureCommentId
.
However, a capture does not necessarily have to be of type Int
so our implementation is a lot more straightforward than the internal Servant one. Most of the seemingly superfluous types you notice here get important when you can pass any kind of type to Servant’s Capture
constructor. We could have stuck closer to how Servant handles things by implementing FromHttpApiData
for our CaptureCommentId
but it might be better to not add too much complexity on top. Suffice to say that if you want this to work on any type you need to implement FromHttpApiData
for that type.
The routing will now first try to parse the next part of the url as an Int and if that does not work it will fail, but in the soft way because there might be other routes that could still match.
Alright, if we now do stack run
we can see
curl localhost:5432/comments/3
"pretend this is comment number 3"⏎
And if we would pass something that isn’t an Int
we get :
curl localhost:5432/comments/fdas
Something went wrong⏎
Cool, we still leverage the internal routing framework but the library is starting to become clearer. Still important to note that our implementations can take shortcuts on the types because we do not tackle generic types. That will become even more the case when we try to parse a full JSON Comment
for instance.
The HasServer instance for a json request payload, ProvideNewComment
Let’s start by creating a shorthand type for supplying a new comment, add a POST and an insert method as well.
data ProvideNewComment = ProvideNewComment
type ExplainApi =
Comments :> ProvideNewComment :> Post '[JSON] NoContent
:<|> Comments
:> CaptureCommentId
:> Get '[JSON] String
insertComment :: NewComment -> Handler String
insertComment = undefined
server :: Server ExplainApi
server = insertComment :<|> getComment
NewComment
is the type we’re already used from some of the earlier blogs, a Comment
without an id.
Because we did not implement any type class yet the compiler will not be happy and inform us of this:
• Couldn't match type ‘ServerT
(NewComment :> Post '[JSON] NoContent) Handler’
with ‘NewComment -> Handler String’
Expected type: Server ExplainApi
Actual type: (NewComment -> Handler String)
:<|> (Int -> Handler String)
A sidestep to :<|>
By the way, it might be good to note that there is an implementation of HasServer
for :<|>
, without which all of this would not be possible. The implementation is rather straightforward, we will descend into both arms of the type tree as soon as the :<|>
is encountered. The implementation is
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m
route Proxy context server = choice (route pa context ((\ (a :<|> _) -> a) <$> server))
(route pb context ((\ (_ :<|> b) -> b) <$> server))
The choice
function is part of the internal router and goes first in the left arm and if that fails it will try to right arm when routing. This is how the firewall-like matching comes about and why very general catch-all rules should be done at the end. The function to serve a directory is a case in point.
The associated type and the hoistServerWithContext function
Anyway, let’s head back to our ProvideNewComment. We need to provide an HasServer instance. The associated type is straightforward. The hoistServerWithContext
follows the exact reasoning as it did for our implementation of CaptureCommentId
but now written more concise it becomes this.
instance (HasServer api context) => HasServer (ProvideNewComment :> api) context where
type ServerT (ProvideNewComment :> api) m = NewComment -> ServerT api m
hoistServerWithContext (Proxy :: Proxy (ProvideNewComment :> api)) proxyContext transformer server = hoistServerWithContext (Proxy :: Proxy api) proxyContext transformer . server
The main complexity here is the routing function, combined with the fact that we of course have to parse a NewComment
along the lines.
The addBodyCheck function
We will first take a side step to check another internal routing function, addBodyCheck
, to achieve this. This function uses the DelayedIO
monad again. Its signature is :
addBodyCheck :: Delayed env (a -> b) -> DelayedIO c -> (c -> DelayedIO a) -> Delayed env b
It’s a bit of a daunting signature. The second and third argument are called the content check
and the body check
. Both can fail, in the DelayedIO monad. We will refer to them as contentCheck and bodyCheck in the next paragraphs, and for clarity we’ll write down the definitions explicitly.
type ContentCheck :: DelayedIO c
type BodyCheck :: (c -> DelayedIO a)
contentCheck
is used to to check the content type of the header and see whether we can do anything with it. Recall that PostNewComment
acts as a replacement for the ReqBody
constructor, which also takes a type, for instance JSON
. Inside the standard implementation of HasServer
for ReqBody
the code needs to check all possible expected content types, check whether one of the provided ones matches with the actual one and return that specific content type (or an error of course).
For instance for the type
ReqBody '[PlainText, JSON] String
the content check function would have to verify whether the content type has text/plain
or application/json
and return the correct deserialization function of the body, and pass it to the body check which will attempt deserialization.
Our implementation will not deal with all possible content types, we will just assume json.
The bodyCheck
function uses the content type to map the body text to the expected haskell data type. So you can see contentCheck and bodyCheck work in tandem, the contentCheck
verifies whether the request has a supported content type and selects a deserialization function, the bodyCheck
tries to deserialize and handles possible errors there.
The first argument of the addBodyCheck
function is the function we want to serve, of the type of our associated type : NewComment -> ServerT api m
. This means that in our case, the type variable a
in the type signature is of type NewComment
. The type variable b
has type ServerT api m
. The only thing we do not know yet is the type of c
.
Finally, the route function
route Proxy context subServer = route (Proxy :: Proxy api) context $ addBodyCheck subServer newCommentContentTypeCheck readNewCommentFromJson
The contentCheck
function will be newCommentContentTypeCheck
and th bodyCheck
will be called readNewCommentFromJson
, defined below.
We can assume, in our oversimplified example, that the content type will be json so there is no need to pass stuff around between the function.
The readNewCommentFromJson
will assume json and try to deserialze or fail accordingly.
newCommentContentTypeCheck :: DelayedIO ()
newCommentContentTypeCheck = withRequest $ \request -> do
let maybeContentTypeHeader = lookup hContentType $ requestHeaders request
case maybeContentTypeHeader of
Just "application/json" -> return ()
_ -> delayedFail err415
readNewCommentFromJson :: () -> DelayedIO NewComment
readNewCommentFromJson _ = withRequest $ \request -> do
bs <- liftIO $ getRequestBodyChunk request
let maybeNewComment = decode' $ cs bs
return $ fromJust maybeNewComment
The real implementation is of course a lot more complicated due to the several possible content types. To indicate how many shortcuts we took here we leave the fromJust
function in.
Let’s illustrate by using curl :
curl --header "Content-Type: application/json" \
--request POST \
--data '{"content":"lots of content"}' \
http://localhost:5432/comments
and before we run this let’s change our implementation of insertComment
to
insertComment :: NewComment -> Handler NoContent
insertComment newComment = do
liftIO $ print $ "Hey we recieved this comment " ++ show newComment
return NoContent
And in our server logs we will see :
"Hey we recieved this comment NewComment {content = \"lots of content\"}"
Okay that was a tour of the internals of the servant library.
One thing we haven’t mentioned is how the route
implementation of the Verb
types is done. We have not because it mainly leverages an internal function methodRouter
and then also deserializes the return type in the preferred way, if any, in similar fashion to the last paragraph.
Because we do not want to implement our own routing framework nor do we want to support several potential types of the return value (JSON, PlainText) in here there is not a lot of added value to dig deeper into the HasServer
implementation for Verb
.
Conclusion
Haskell Servant looks a lot like black magic from the outside. When digging deeper into it, you can see it mainly consists of a well-chosen recursive type family, combined with data kinds and a good routing framework.
The routing framework’s complexity mainly stems from the fact that it cannot be specific, unlike our implementations in this blog. The routing framework needs to take into account any possible content type and serialization/deserialization function, as well as content types that are not present in the base Haskell Servant library. An example can be found here.
The final piece of the puzzle is the hoistServerWithContext
function which gives us an escape hatch to run in a different monad than the standard Handler
, if we want to.