Deprecating API endpoints with Servant

Ben Weitzman
Co–Star
Published in
9 min readMay 16, 2019
Sebastien Gabriel @sgabriel (https://unsplash.com/photos/-IMlv9Jlb24)

Introduction

API design is hard.

As we grow Co–Star, we find ourselves occasionally wanting to deprecate endpoints in our API. There are many reasons why we may want to stop supporting old endpoints: we might get things wrong in the architecture, remove an old endpoint for a feature we no longer support, or fix a security vulnerability.

servant is a web framework for Haskell that enables the specification of an entire API as a type. At Co–Star, we use servant to write our backend, and we’ve had a lot of success using the type of our API to help us generate tests and documentation. I wanted to extend some of servant’s behavior to help us model deprecated endpoints as well.

I had two goals in mind:

1 . Automatically tell clients that they are hitting a deprecated http endpoint. While not a standard, there is a draft for a sunset HTTP header spec that we could use.

2. Keep track of which endpoints are deprecated so that we can drop support when we are ready.

(This blog post is generated from a literate Haskell file. The source code alone can be seen here.)

Before we get to the code, let’s introduce the cast of characters:

module Servant.Deprecated whereimport Data.List
import Data.Proxy
import Data.String.Conv
import Data.Time
import GHC.TypeLits
import Network.HTTP.Date
import qualified Network.HTTP.Types as HTTP
import Network.Wai
import Servant

Automatic sunset header injection

At the core of servant lies a handful of types that describe different facets of an API and its HTTP endpoints. These include things like the path components, query params, bodies, etc. These different facets can be combined together with the help of combinators to form larger and more complicated endpoints.

Our first step is to introduce a new type that can be used to annotate API endpoints, marking them as deprecated.

In our annotation we include a date (specified at the type level using Nats) on which we would like to drop support for our deprecated endpoint.

data Deprecated (year :: Nat) (month :: Nat) (day :: Nat)

Notice that we don’t have to include a constructor for this type because it is only going to be used at the type level.

It’s important for us to not drop support for endpoints that are still actively in use. Setting a date in the future allows us to monitor how many people are still using deprecated endpoints. More on that later.

Now that we have our annotation, we want automatically inject information in our endpoints’ response headers in order to let clients know they are hitting outdated endpoints.

servant uses a typeclass to build up routers for big APIs from small pieces. The typeclass constraint here says that if we have an API we know how to handle, then we also know how to handle a deprecated version of that api. KnownNat helps us turn type level numbers into value level number.

instance (KnownNat year
,KnownNat month
,KnownNat day
,HasServer api ctx
) => HasServer (Deprecated year month day :> api) ctx where

The ServerT type family transforms the type of an api into the type of its handler. For example, if an endpoint is described by the type Get ‘[JSON] String, then its handler might look like return “hello world". If the type indicates a capturing segment like Capture "UserId" Int :> Get '[JSON] String, then its handler would look more like \userId -> return $ “hello user “ ++ show userId.

Deprecating an endpoint doesn’t change the type of its handler, so we return the same handler as the non-deprecated api type.

  type ServerT (Deprecated year month day :> api) m = ServerT api m

We do, however, want to change the responses of the endpoint. The route function describes how requests are routed through an api, matching paths and methods and testing capture groups until a matching endpoint is found.

The result of this function is a Router env, and fortunately for us, servant provides a method tweakResponse which will allow us to inject our sunset header.

  route _ ctx dlyd =
let sub = route (Proxy :: Proxy api) ctx dlyd
in tweakResponse (fmap addSunsetHeader) sub

where

Headers in servant are represented as a list, so we just add in our new header:

    addSunsetHeader :: Response -> Response
addSunsetHeader = mapResponseHeaders (sunsetHeader:)

The sunset spec says that the dates should be in a particular format, so we do a little wrangling to get things in the right format:

    sunsetHeader :: HTTP.Header
sunsetHeader = (“Sunset”
, formatHTTPDate $ utcToHTTPDate sunsetDate
)
sunsetDate :: UTCTime
sunsetDate = UTCTime sunsetDay 0

In order to turn our type level deprecation date (of kind Nat) into a concrete header value (of type Integer) we use type level literal reflection utilities provided by GHC:

    sunsetDay :: Day
sunsetDay = fromGregorian
(natVal $ Proxy @year)
(fromIntegral . natVal $ Proxy @month)
(fromIntegral . natVal $ Proxy @day)

Since we’re not changing the handler type, we don’t have to change the way we hoist that handler.

  hoistServerWithContext _ = hoistServerWithContext (Proxy @api)

That’s all we have to change in order to start getting deprecation headers in our responses.

Testing the sunset header

We can create a little API to test this out:

type TestAPI =
Deprecated 2019 5 1 :> Get '[JSON] String
:<|> "real" :> Get '[JSON] Bool
testAPI :: Server TestAPI
testAPI =
return "I'm deprecated!"
:<|> return True

In GHCI, we can then use warp to server our API:

> import qualified Network.Wai.Handler.Warp as W
> W.run 5150 $ serve @TestAPI Proxy testAPI

We can now try curling our little server to hit our deprecated endpoint

> curl localhost:5150 -i
HTTP/1.1 200 OK
Transfer-Encoding: chunked
Date: Fri, 26 Apr 2019 20:21:42 GMT
Server: Warp/3.2.22
Sunset: Tue, 01 May 2019 00:00:00 GMT
Content-Type: application/json;charset=utf-8
"I'm deprecated!"

And our non-deprecated endpoint

> curl localhost:5150/real -i
HTTP/1.1 200 OK
Transfer-Encoding: chunked
Date: Fri, 26 Apr 2019 20:22:41 GMT
Server: Warp/3.2.22
Content-Type: application/json;charset=utf-8
true

Using sunset headers in the clients

Now that clients have this info, they can help facilitate the migration to non-deprecated versions of the API.

Clients could log a warning (or an error if they are past the deprecation date). Aggregating this information could help lend confidence to a decision to remove support for an old endpoint.

For example, if 10% of clients are still on an outdated version, we’re not ready to drop support, even if we’re past the support date. It would be better to focus on getting old clients to upgrade and revisit in a month.

Another possibility would be to prompt users to upgrade to a new version if their clients are being notified that they are hitting deprecated endpoints.

Tooling for dropping support of deprecated endpoints

With our first goal completed we turn our attention to tools that will help us deal with deprecated endpoints after their sunset date.

We’re going to want to compare the type level dates in our API type to the current date when we run our tools. That date will exist at the value level from getCurrentTime. So the first step to comparing these is to define a value-level representation of the API that we can reflect to from the type level. To do this, we model different parts of our endpoints as data types.

Paths are composed of literal segments and named capture groups:

data Path = Segment String | Capture String

Endpoints have a list of path segments, a method, and the date that they may be deprecated on:

data Endpoint = Endpoint
{ method :: String
, path :: [Path]
, deprecatedOn :: Maybe Day
}

We can write a custom show instance for our endpoints that will display them in the familiar GET /user/:user_id/friends format:


instance Show Path where
show (Segment x) = x
show (Capture y) = ‘:’ : y
instance Show Endpoint where
show Endpoint{..} = mconcat
[ method
, “ /”
, intercalate “/” (show <$> path)
]

Then, we create a helper function for modifying an Endpoint to include a new path component by adding it to the front of the endpoint’s path list:

addPath :: Path -> Endpoint -> Endpoint
addPath newPath Endpoint{..} = Endpoint
{ path = newPath : path
, ..
}

We can now define a new typeclass that will reflect the type level API into a value level list that we can process:

class DescribeApi api where
describe :: Proxy api -> [Endpoint]

This typeclass and its instances have a fairly similar structure to the HasServer typeclass we saw earlier. We can build up ways to describe bigger APIs from the knowledge about how to describe smaller ones.

Let’s start with the smallest unit of the API in servant, the request verb. When all we know about the endpoint is the verb, the path is empty and the endpoint is not deprecated:

instance ReflectMethod method => 
DescribeApi (Verb method s c a) where
describe _ =
[Endpoint
{ method = toS $ reflectMethod @method Proxy
, path = []
, deprecatedOn = Nothing
}
]

If we know how to describe an API, we can also describe the API if it comes after a path, we just have to insert the new path segment into all the endpoints:

instance (KnownSymbol path, DescribeApi api) => 
DescribeApi (path :> api) where
describe _ =
let sub = describe @api Proxy
in addPath (Segment $ symbolVal @path Proxy) <$> sub

Similarly for capturing info from the path:

instance (KnownSymbol path, DescribeApi api) => 
DescribeApi (Capture path a :> api) where
describe _ =
let sub = describe @api Proxy
in addPath (Capture $ symbolVal @path Proxy) <$> sub

The description of a combination of endpoints is the concatenation of each endpoint’s description:

instance (DescribeApi a, DescribeApi b) => 
DescribeApi (a :<|> b) where
describe _ =
let left = describe @a Proxy
right = describe @b Proxy
in left ++ right

Any API can be deprecated by adding the sunset date to all of the endpoints:

instance (KnownNat y, KnownNat m, KnownNat d, DescribeApi api) =>
DescribeApi (Deprecated y m d :> api) where
describe _ =
let sub = describe @api Proxy
year = natVal @y Proxy
month = fromIntegral $ natVal @m Proxy
day = fromIntegral $ natVal @d Proxy
sunsetDay = fromGregorian year month day
in addDeprecated sunsetDay <$> sub
where
addDeprecated :: Day -> Endpoint -> Endpoint
addDeprecated day Endpoint{..} = Endpoint
{ deprecatedOn = Just day
, ..
}

The above isn’t quite sufficient to let us describe all APIs expressible in the full language of servant (which include things like authorization and query params), but it’s a start. Further support is left as an exercise to the reader.

And now for the payoff, we can reflect our APIs into values and then filter them based on the deprecation date:

deprecatedEndpoints :: DescribeApi api 
=> Proxy api
-> UTCTime
-> [Endpoint]
deprecatedEndpoints p time =
let endpoints = describe p
in filter deprecated endpoints
where deprecated :: Endpoint -> Bool
deprecated Endpoint{ deprecatedOn = Nothing } = False
deprecated Endpoint{ deprecatedOn = Just deprecatedDate } =
time >= UTCTime deprecatedDate 0

Dropping into GHCI to test, we can see that we have no deprecated endpoints past their date as of 4/1/19:

> deprecatedEndpoints @TestAPI Proxy (UTCTime (fromGregorian 2019 4 1) 0)
[]

But things change in May:

> deprecatedEndpoints @TestAPI Proxy (UTCTime (fromGregorian 2019 5 1) 0)
[GET /]

One way to use this would be set up a recurring job that posts to slack when there’s an endpoint we’re ready to drop support for. That way we don’t have to keep track of this in a ticket system, it’s built right in to the code.

Another option would be to use template Haskell to generate warnings (or even type errors!) for endpoints that are ready to be removed.

Summary

At Co–Star, we like to use types not just to verify programs, but more broadly as a cornerstone of our application development process. By using techniques like type-driven development, documentation generation, and type directed static analysis, we can spend less time working on tedious parts of programming and more time focusing on the interesting, challenging, and impactful aspects of engineering.

(If that sounds like something that you agree with, we’re hiring! Drop us a line through our jobs page)

The code of this post can be found here

--

--