Guarantee Authentication via Haskell's Type System

Writing a Haskell API Server, Part 3

In part 1 of our series on writing a JSON API in Haskell, Chris and I discussed fully utilizing the database in an application. In part 2 we proceeded to closely mirror our domain logic using Haskell types and typeclasses. Today, in part 3, we’ll take domain modeling a step further by guaranteeing user authentication for our JSON API at the type level.

From experience, we know that security is complex in theory but comparatively simple— though error-prone!— in implementation. Using Haskell’s type system and what we’ve learned from previous parts, we can keep a simple security implementation while almost completely removing the possibility of error.

Surely, We Can Do Better

Our API uses the Scotty library to handle request routing and the Hasql library for database access. If you’re familiar with Ruby’s Sinatra gem, the structure of Scotty is similar. A basic REST-styled Scotty/Hasql application has types like…

module MyApp.Server

import Hasql
import Hasql.Postgres
import Web.Scotty

type MyServer s = ScottyT MyException (Tx Postgres s IO)
type MyAction s = ActionT MyException (Tx Postgres s IO)

and a definition like…

module Main where

import Hasql
import Web.Scotty
import MyApp.Server

import qualified MyApp.Controllers.Resource as Resource

main :: IO ()
main =
    session myPgConfig mySessConfig $ do
      database <- unliftSession
      scottyT 3000 id database routes

routes :: MyServer s ()
routes = do
    get    "/resources"              $ Resource.list
    post   "/resources"              $ Resource.create
    get    "/resources/:resource_id" $ Resource.show
    post   "/resources/:resource_id" $ Resource.edit
    delete "/resources/:resource_id" $ Resource.destroy

…where :resource_id is captured as a parameter that is available to a respective handler. One such handler, Resource.show, might look something like…

module MyApp.Resource where

show :: MyAction s ()
show = do
    rid <- param "resource_id"
    json $ findResource rid

This simple structure works great for public APIs, but what happens when we need a private API requiring user authentication? We could add something like the following to our show function…

show :: MyAction s ()
show = do
    uid <- param "user_id"
    authenticateUser $ User.find uid
    -- the rest of our function

…but this way is fraught with vulnerability. Forgetting these lines on a critical function would create an immediate security hole. We could write specs (using the fantastic Hspec.WAI library) to hopefully guard against this, but with Haskell we can do better.

It’s About the Users!

Before we start typing, let’s think about what a private API route entails. A private route belongs to a particular user (or group of users) because some result of that route depends on an attribute of the user.

Retrieving a user requires identifying a user and providing their secure token— a “login” of sorts. No user should be accessible without their login, and failure to retrieve a user should bounce anybody attempting to access a private route.

Now that we’ve identified the key components of a private route, let’s model them in Haskell. First, we’ll define some shared types, following the pattern of newtyping described in part 2:

newtype UserId    = UserId Int
newtype UserToken = UserToken ByteString

Next, we define the more-complex datatypes using these newtypes. (Note the pattern of prefacing record field accessors with a [recordName]_. This is because record accessor naming in Haskell is currently terrible.)

data User = User
  { user_id :: UserId
  , -- any other user attributes
  }

data Login = Login
  { login_userId :: UserID
  , login_userToken :: UserToken
  }

We know that any private controller action requires a user; let’s change the type signature of our example action to reflect that.

show :: User -> MyAction s ()
show user = do
    -- the rest of the function

Finally, we know that the only way a controller action can obtain a user is through authentication, and that authentication must retrieve the user via a login. Let’s write these approximate type signatures, then figure out their function definitions.

Scotty routes accept an ActionM () as their last argument. Since our private controller actions now require a user, authentication must happen between when a route is matched and an action is called, like so:

routes :: MyServer s ()
routes = do
    get "/resources/:resource_id" $ User.authenticate Resource.show

which gives it the following type signature:

authenticate :: (User -> (forall s. MyAction s ())) -> MyAction s ()
authenticate = undefined

We also know we’ll need something with the following type to retrieve our user via a Login. Relying on Hasql, we can do:

findByLogin :: Login -> Tx Postgres s (Maybe User)
findByLogin login = undefined

Where Tx Postgres s is the Hasql transaction monad, which is run via our runQuery function (that can otherwise be ignored for this post).

Filling in the Blanks

Now that our types align, all that’s left for us to have type-enforced user authentication is to define the two functions findByLogin and authenticate.

In part 1 of our series, we demonstrated two functions for creating and retrieving users, which use PostgreSQL’s pgcrypto extension to handle all user lookup and token creation and verification. So, assuming we have a user table with the following SQL schema:

CREATE TABLE users (
  id          INTEGER PRIMARY KEY,
  token_hash  VARCHAR NOT NULL,
  -- any other user attributes
);

…we can update the previously-described findByLogin function to become:

findByLogin :: Login -> Tx Postgres s (Maybe User)
findByLogin (Login userId userToken) =
    single $ [q|
      SELECT id, -- any other user columns
      FROM users
      WHERE id = ? AND crypt(?, token_hash) = token_hash
    |] userId userToken

Now that we can retrieve users via their login, we can define the authenticate function. Before we do, though, let’s describe how it should work. Given a route, authenticate must:

  • retrieve the UserID from the request parameters
  • retrieve the UserToken from the HTTP authorization header
  • create a Login
  • retrieve the user from the database with this Login
  • if the retrieval succeeds, pass the user to the route
  • if the retrieval fails, return an HTTP 401

That sounds like a lot! Thankfully, Haskell is nothing if not concise. Let’s see what this looks like in practice. To simplify, we’ll split this list into two functions— one that creates the Login from a request, and another to authenticate a user for a controller action:

fromRequest :: MyAction s Login
fromRequest = do
    uid   <- param "user_id"
    token <- header "Authorization"

    case LT.words <$> token of
      Just ["Token", t] -> return $
        Login (UserID uid) (UserToken $ LT.toStrict t)
      _ -> raise MissingAuthToken

authenticate :: (User -> forall s. MyAction s ()) -> MyAction s ()
authenticate routeFor = do
    login <- fromRequest
    user  <- runQuery $ User.findByLogin login

    case user of
      Just u -> routeFor u
      _      -> raise UnauthorizedUser

Don’t let the raise function confuse you; this doesn’t break program control flow as do exceptions in imperative languages. Instead, it forces the Scotty monad to the error equivalent of the Either type, which— when the monad is resolved— must be explicitly handled.

What We Have

Let’s look back at what we’ve created to understand the significance of the architecture.

  1. We have only one way to generate a Login— the fromRequest function— which uses HTTP params and headers.
  2. We have only one way to find a User— the findByLogin function, which matches a User by their UserID and UserToken.
  3. We’ve given our private controller actions a new type, User -> MyAction s (), which requires a User to type check as a Scotty route handler.
  4. The only way to supply a User to a private controller action is via the authenticate function, which takes a private controller action and makes the MyAction s () type that matches what Scotty expects.

Putting everything together, we cannot call a private API route without first authenticating a User because attempting to do so wouldn’t type-check— and therefore wouldn’t compile. Using Haskell’s type system, we’ve eliminated nearly all vectors for error, ensuring that an application bug won’t be the source of an authentication lapse in our API (without requiring significant programming work-arounds).

That’s it for part 3 of writing an API server in Haskell! We hope you’ll be around for part 4, so that we can share more of what we’ve learned from this endeavor.

Posts in this series

  • Actually Using the Database
  • Writing a Haskell API Server, Part 2
  • Guarantee Authentication via Haskell's Type System
  • Writing a Haskell API Server, Part 4