Generating the Docker client with servant-client

- January 24, 2017
Kwang's Haskell Blog - Generating the Docker client with servant-client

Generating the Docker client with servant-client

Posted on January 24, 2017 by Kwang Yul Seo

Servant provides a type-level DSL for declaring web APIs. Once we write the specification with the DSL, we can do various things including:

  • Write servers (this part of servant can be considered a web framework),
  • Obtain client functions (in Haskell),
  • Generate client functions for other programming languages,
  • Generate documentation for your web applications

The primary use case of Servant is to write servers, but we can use servant-client to generate client functions for the pre-existing web servers too! In this post, I will show you how we can generate client functions for the Docket remote API automatically with servant-client.

API specification

To make the exposition simple, we will specify only three APIs: ping, version and containerList.

The simplest API is Ping which tests if the server is accessible. Its path is /v1.25/_ping and it returns OK as a plain text with status code 200. We can succinctly describe this endpoint with Servant’s type-level DSL.

type Ping = "_ping" :> Get '[PlainText] Text

Version is a slightly more complex API which returns the version information as JSON. Version data type has the required fields and it declares an instance of FromJSON for unmarshalling JSON data into Version. fieldLabelModifier is used to bridge JSON field names to Version field names.

type Version = "version" :> Get '[JSON] Version

data Version = Version
  { versionVersion       :: Text
  , versionApiVersion    :: Text
  , versionMinAPIVersion :: Text
  , versionGitCommit     :: Text
  , versionGoVersion     :: Text
  , versionOs            :: Text
  , versionArch          :: Text
  , versionKernelVersion :: Text
  , versionExperimental  :: Bool
  , versionBuildTime     :: Text
  } deriving (Show, Eq, Generic)

instance FromJSON Version where
  parseJSON = genericParseJSON opts
    where opts = defaultOptions { fieldLabelModifier = stripPrefix "version" }

stripPrefix :: String -> String -> String
stripPrefix prefix = fromJust . DL.stripPrefix prefix

Finally, ContainerList returns the list of containers. The API takes optional query parameters such as all, limit, size and filters as specified follows. We created a newtype wrapper for ContainerID and declared FromJSON instances for ContainerID and Container. Some fields are omitted for brevity.

type ContainerList = "containers" :> "json" :> QueryParam "all" Bool
                                            :> QueryParam "limit" Int
                                            :> QueryParam "size" Bool
                                            :> QueryParam "filters" Text
                                            :> Get '[JSON] [Container]

newtype ContainerID = ContainerID Text
  deriving (Eq, Show, Generic)

instance FromJSON ContainerID

data Container = Container
  { containerId               :: ContainerID
  , containerNames            :: [Text]
  , containerImage            :: Text
  , containerImageID          :: ImageID
  , containerCommand          :: Text
  , containerCreated          :: Int
  -- FIXME: Add Ports
  , containerSizeRw           :: Maybe Int
  , containerSizeRootFs       :: Maybe Int
  -- FIXME: Add Labels
  , containerState            :: Text
  , containerStatus           :: Text
  -- FIXME: Add HostConfig
  -- FIXME: Add NetworkSettings
  -- FIXME: Add Mounts
  } deriving (Show, Eq, Generic)

Our API is just the combination of these endpoints.

type Api = Ping :<|> Version :<|> ContainerList

API Versioning

Because the Docker remote API has many versions, it adds a version prefix in the path. Servant allows us to expression this version scheme by declaring a new Api with the version prefix.

type ApiV1_25 = "v1.25" :> Api

We can also mix-and-match many endpoints as the Docker remote API changes. Let’a assume that the docker API version v1.26 changed the specification of the Version endpoint. We can reuse unchanged endpoints by replacing only the changed endpoints with new ones.

type Version1_26 = ...
type ApiV1_26 = "v1.26" :> (Ping :<|> Version1_26 :<|> ContainerList)

Generating Client Functions

Now it’s time to generate client functions from the specification. It’s super easy! We can simply pass our API to client function.

ping :: ClientM Text
version :: ClientM Version
containerList' :: Maybe Bool -> Maybe Int -> Maybe Bool -> Maybe Text -> ClientM [Container]

ping
  :<|> version
  :<|> containerList' = client apiV1_25

ping and version functions are okay, but the signature containerList' is a bit confusing. We have to pass four Maybe values and two of them have the Bool type and it is not easy to remember the order of the arguments. We can improve the function by declaring a wrapper function containerList. It takes a ContainerListOptions, and the users of the function can pass defaultContainerListOptions as the default value.

data ContainerListOptions = ContainerListOptions
  { containerListOptionAll     :: Maybe Bool
  , containerListOptionLimit   :: Maybe Int
  , containerListOptionSize    :: Maybe Bool
  , containerListOptionFilters :: Maybe Text
  } deriving (Eq, Show)

defaultContainerListOptions :: ContainerListOptions
defaultContainerListOptions = ContainerListOptions
  { containerListOptionAll     = Just False
  , containerListOptionLimit   = Nothing
  , containerListOptionSize    = Just False
  , containerListOptionFilters = Nothing
  }

containerList :: ContainerListOptions -> ClientM [Container]
containerList opt = containerList' (containerListOptionAll opt)
                                   (containerListOptionLimit opt)
                                   (containerListOptionSize opt)
                                   (containerListOptionFilters opt)

Because the expressiveness of Haskell is much more powerful than that of the REST API specification, these wrappings are somewhat unavoidable to make our client functions more Haskell-friendly.

Using Client Functions

Now our client functions for the Docker API is ready. We need to prepare a ClientEnv by passing the host, port and url prefix of the server. We also created a custom connection manager which uses the domain socket for communication because the Docker server listens on the domain socket by default. Interested readers are referred to my previous article Custom connection manager for http-client for the implementation details of newUnixSocketManager.

query :: ClientM [Container]
query = do
  ok <- ping
  liftIO $  print ok
  version <- version
  liftIO $ print (versionVersion version)
  containerList defaultContainerListOptions

app :: String -> Int -> IO ()
app host port = do
  manager <- newUnixSocketManager "/var/run/docker.sock"
  res <- runClientM query (ClientEnv manager (BaseUrl Http host port ""))
  case res of
    Left err          -> putStrLn $ "Error: " ++ show err
    Right containers  -> mapM_ print containers

Because ClientM is a monad, we can combine multiple monadic actions into one. query function pings the server, queries the version information and then request the list of containers.

Swagger

So far I manually specified the API with Servant’s DSL, but if the server has the Swagger specification we can even generate the Servant DSL from the Swagger specification. swagger-codegen has the HaskellServantCodegen, so we can use it! (I haven’t tried it yet.)

Wrap-up

Writing client functions for existing servers are boring and repetitive. With servant-client, we no longer need to write these functions. We just specify the API and Servant writes the client functions for us. Have fun with Servant!

Read more

How Servant's type-safe links work

- January 20, 2017
Kwang's Haskell Blog - How Servant's type-safe links work

How Servant's type-safe links work

Posted on January 20, 2017 by Kwang Yul Seo

Many Haskell web frameworks provide so called type-safe links. Servant is no exception and it provides one of the strongest safety check. It statically guarantees that all links are valid endpoints of the server!

In servant, we can create a type-safe URI using safeLink function. It takes both the whole API and the API endpoint we would like to point to. It signals a type error if the endpoint does not belong to the whole api.

-- | Create a valid (by construction) relative URI with query params.
--
-- This function will only typecheck if `endpoint` is part of the API `api`
safeLink
    :: forall endpoint api. (IsElem endpoint api, HasLink endpoint)
    => Proxy api      -- ^ The whole API that this endpoint is a part of
    -> Proxy endpoint -- ^ The API endpoint you would like to point to
    -> MkLink endpoint

To better explain how type-safe links work in Servant, let’s create a mini web DSL that is a small subset of Servant DSL.

{-# LANGUAGE DataKinds              #-}
{-# LANGUAGE ConstraintKinds        #-}
{-# LANGUAGE PolyKinds              #-}
{-# LANGUAGE TypeFamilies           #-}
{-# LANGUAGE TypeOperators          #-}
{-# LANGUAGE UndecidableInstances   #-}

import Data.Proxy
import GHC.Exts (Constraint)
import GHC.TypeLits

data a :<|> b = a :<|> b
infixr 8 :<|>

data (path :: k) :> a
infixr 9 :>

data Method = Get | Post
  • (:<|>) is the union of two APIs.
  • (:>) specifies the path.
  • Support only two methods Get and Post

Here’s the API and a few endpoints defined using our mini web DSL.

type Api = "item" :> Get
      :<|> "item" :> Post
      :<|> "user" :> Get

type ValidEndpoint = "item" :> Get

type InvalidEndpoint1 = "user" :> Post
type InvalidEndpoint2 = "none" :> Get

For simplicity, our safeLink function is also revised to return () instead of creating an actual URI. Creating a URI from the endpoint is straightforward.

Our mini safeLink throws an type error if endpoint does not belong to api. But how? The body of safeLink is just ()!

safeLink :: forall endpoint api. (IsElem endpoint api) => Proxy api -> Proxy endpoint -> ()
safeLink _ _ = ()

An acute reader might have noticed, the magic is hidden in the IsElem type function. IsElem endpoint api checks if endpoint is an element of api.

Before diving into the definition of IsElem, we need an auxiliary type-level function Or. It is defined using closed type families.

-- | If either a or b produce an empty constraint, produce an empty constraint.
type family Or (a :: Constraint) (b :: Constraint) :: Constraint where
    -- This works because of:
    -- https://ghc.haskell.org/trac/ghc/wiki/NewAxioms/CoincidentOverlap
    Or () b       = ()
    Or a ()       = ()

Or takes two constraints as arguments and produces an empty constraint if either one of two arguments produces an empty constraint.

IsElm is defined in terms of Or.

-- | Closed type family, check if endpoint is within api
type family IsElem endpoint api :: Constraint where
    IsElem e (sa :<|> sb)                   = Or (IsElem e sa) (IsElem e sb)
    IsElem (e :> sa) (e :> sb)              = IsElem sa sb
    IsElem e e                              = ()

The rules are straightforward:

  1. If api consists of multiple endpoints, check each endpoint and combines the result using Or.
  2. If both api and endpoint start with the same path e, check the remaining parts.
  3. If both api and endpoint is the same, return an empty constraint.

If endpoint does not belong to api, GHC can’t deduce the type and emits an type error. The actual implementation of Servant is more complicated because it needs to handle other components such as Capture and QueryParam, but the core idea is the same!

Now we can test if our safeLink actually works.

getItem is well-typed because ValidEndpoint is in fact a valid endpoint of Api using safeLink.

getItem  = safeLink (Proxy :: Proxy Api) (Proxy :: Proxy ValidEndpoint)
postUser = safeLink (Proxy :: Proxy Api) (Proxy :: Proxy InvalidEndpoint1)

postUser is ill-typed because InvalidEndpoint1 is not a valid endpoint of Api. We can see that GHC actually throws an error!

• Could not deduce: Or
                      (IsElem ("user" :> 'Post) ("item" :> 'Get))
                      (Or
                         (IsElem ("user" :> 'Post) ("item" :> 'Post))
                         (IsElem ("user" :> 'Post) ("user" :> 'Get)))
    arising from a use of ‘safeLink’
• In the expression:
    safeLink (Proxy :: Proxy Api) (Proxy :: Proxy InvalidEndpoint1)
  In an equation for ‘postUser’:
      postUser
        = safeLink (Proxy :: Proxy Api) (Proxy :: Proxy InvalidEndpoint1)
Read more

Natural transformations in Servant

- January 18, 2017
Kwang's Haskell Blog - Natural transformations in Servant

Natural transformations in Servant

Posted on January 18, 2017 by Kwang Yul Seo

I’ve recently started using servant at work. Servant lets us declare web APIs at the type-level once and use those APIs to write servers, obtains client functions and generate documentation. It’s a real world example which shows the power of Haskell type system.

The most interesting part of Servant is its extensible type-level DSL for describing web APIs. However, I found another interesting application of theory into practice in servant-server library. It is the use of natural transformation to convert one handler type into another handler type.

In Servant, Handler is a type alias for ExceptT ServantErr IO.

type Handler = ExceptT ServantErr IO

Thus Handler monad allows us to do:

  • Perform IO operations such as database query through the base monad IO.
  • Throw a ServantErr if something went wrong.

Here’s an example of a Servant handler.

type ItemApi =
    "item" :> Capture "itemId" Integer :> Get '[JSON] Item

queryItemFirst :: Integer -> IO (Maybe Item)
queryItemFirst itemId = ...

getItemById :: Integer -> Handler Item
getItemById itemId = do
  mItem <- liftIO $ queryItemFirst itemId
  case mItem of
    Just item -> return item
    Nothing   -> throwError err404

So far so good, but what if queryItemFirst needs a database connection to retrieve the item? Ideally, we would like to create a custom monad for our application such as

data AppEnv = AppEnv { db :: ConnectionPool }
type MyHandler = ReaderT AppEnv (ExceptT ServantErr IO)

queryItemFirst :: ConnectionPool -> Integer -> IO (Maybe Item)
queryItemFirst cp itemId = ...

getItemById :: Integer -> MyHandler Item
getItemById itemId = do
  cp <- db <$> ask
  mItem <- liftIO $ queryItemFirst cp itemId
  case mItem of
    Just item -> return item
    Nothing   -> throwError err404

Unfortunately, this does not work because serve wants Handler type. We need a way to transform MyHandler into Handler so that Servant can happily serve our handlers. Because both MyHandler and Handler are monads, we need a monad morphism. Or more generally, we need a natural transformation from MyHandler to Handler.

Servant provides a newtype wrapper Nat which represents a natural transformation from m a to n a.

newtype m :~> n = Nat { unNat :: forall a. m a -> n a}

So what we want is MyHandler :~> Handler.

myHandlerToHandler :: AppEnv -> MyHandler :~> Handler
myHandlerToHandler env = Nat myHandlerToHandler'
  where
  myHandlerToHandler' :: MyHandler a -> Handler a
  myHandlerToHandler' h = runReaderT h env

Okay, now we can get a natural transformation MyHandler :~> Handler by applying an AppEnv to myHandlerToHandler. How can I tell the Servant to use this natural transformation to serve our handlers? That’s what enter does!

server :: AppEnv -> Server ItemApi
server env =
  enter (myHandlerToHandler env) getItemById

Wrapping Handler with ReaderT is a common idiom, so Servant provides a convenient function runReaderTNat which is exactly the same to myHandlerToHandler. So we can rewrite server as follows:

server :: AppEnv -> Server ItemApi
server env =
  enter (runReaderTNat env) getItemById

Servant also provides a lot of monad morphisms such as hoistNat, embedNat, squashNat and generalizeNat. Sounds familiar? These are just wrappers around mmorph library functions. Interested readers are referred to Gabriel Gonzalez’s article mmorph-1.0.0: Monad morphisms.

In object-oriented programming, we use Adapter pattern to allow the interface of an existing class to be used as another interface. In functional programming, we use natural transformations (or more generally, functors) to do so!

Read more