Build Your Own Haskell Web Framework on WAI

April 19, 2015 (Updated, April 15, 2024)

This article shows how you can build on top of the basic request/response handling functionality provided by WAI and the Warp server, to support some of the requirements you might have in a typical web application. The content is mostly gleaned from my research into the code of several WAI-based web frameworks to try to understand how they work. Building a web application was one of the things I tackled when I didn’t really know Haskell well enough, so hopefully this will be useful if you’re at a similar stage and would like to understand what’s going on in a bit more depth. I’ll outline some of the features these frameworks add, build a similar (but simplified) implementation, and also provide links to the source code of some real-world frameworks built on WAI (such as Scotty, Spock and Yesod) for comparison.

Whether you need to use an additional framework on top of WAI will very much depend on your requirements, how complicated your application is and whether you want to track the extra dependencies in your project. Frameworks cater for general cases (making the types more complex for a beginner) and they have a lot of features. You should certainly try out something like Spock or Scotty as they are easy to get started with. For a simple application, or one where you need finer control over handling requests, you might then consider a customized approach. On the other hand, you might overlook something important which the framework authors didn’t 1 – the code in this article is only meant to be a rough outline. If you do decide to “build your own,” please think hard before releasing it to Hackage. There are more than enough WAI frameworks out there already 2.

Basic WAI

WAI (“web application interface”) is a Haskell HTTP request/response API. Theoretically it is server-agnostic but in practice it is really only implemented by the warp server.

Request handling in WAI is defined by the Application type 3 :

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived

The Request gives access to the request headers, query string, request body and so on, while the Response -> IO ResponseReceived callback allows us to send a response we have created. A typical WAI example you might come across will show how to send a simple response:

{-# LANGUAGE OverloadedStrings #-}
import Network.HTTP.Types (status200)
import Network.Wai
import Network.Wai.Handler.Warp (run)

app :: Application
app _ respond = respond $
  responseLBS status200 [("Content-Type", "text/plain")] "hello"

main = run 3000 app

So from a web developer’s perspective, a WAI application is a single function which is called for each request and sends back a response. The code runs in the IO monad and there’s no out-of-the-box support for performing redirects, cookie handling, managing sessions or supporting different response types such as text, HTML or JSON. Web frameworks like Scotty and Yesod build these features on top of WAI using their own custom handler monads, meaning you won’t usually call the WAI functions directly in your code. Frameworks also provide some kind of routing DSL, usually based on the request path and method (GET, POST etc.), so you can map different requests to different handler functions.

The Handler Monad

The handler monad provides convenient (read-only) access to the request (headers, parameters) and also provides functions to build the response. This is typically achieved using a combination of ReaderT and StateT monad transformers 4 5. So we could start with something like

{-# LANGUAGE OverloadedStrings #-}

import Control.Monad.Reader
import Control.Monad.State
import Data.Map.Strict (Map)
import Data.Text (Text)
import qualified Data.ByteString.Lazy as BL
import Network.HTTP.Types (ResponseHeaders, Status)
import Network.Wai (Request)


type Params = Map Text [Text]

data RequestData = RequestData
    { waiReq :: Request
    , queryParams :: Params
    , postParams  :: Params
    }

data ResponseState = ResponseState
    { resStatus :: Status
    , resHeaders :: ResponseHeaders
    , content :: BL.ByteString
    }

type Handler a = ReaderT RequestData (StateT ResponseState IO) a

RequestData provides access to the original WAI request as well as the parsed request parameters and is accessed via the reader monad. ResponseState stores the status code, headers and response content. Here we’re assuming the only requirement is to handle simple content we can create as a ByteString, so we’re forgetting about streaming responses or serving up files directly. Similarly we’re ignoring file uploads in the request data 6.

Routing

Our application will consist of request handler functions written in the Handler monad. We also need some way of mapping different requests to the correct handlers. Frameworks generally include a DSL to do this, often using Sinatra-style verb/path combinations, including support for capturing URL parameters and converting parameters to specific types.

A very simple routing option is to just pattern match on the pathInfo property of the WAI Request, which is of type [Text]:

type Router = [Text] -> Handler ()

We can then build our application as a simple routing table:

myAppRouter :: Router
myAppRouter path = case path of
  ["home"]    -> myHomePageHandler
  ["login"]   -> loginHandler
  ["logout"]  -> logoutHandler
  ["user", u] -> userHandler u
  _           -> notFound

For a given request, the router will give us a corresponding handler which we can run. The type is Handler () since the handler doesn’t return anything. The ResponseState retrieved from the State monad gives us all we need to send the response. This isn’t a very flexible approach, but it’s very easy to understand and fine as a first option if we don’t need to be able to compose routers and so on. You can find routing packages on Hackage but that’s a topic for another time.

Running the Handler

What does it actually mean to run the handler? Before we look at the code, we need to make some minor changes to the Handler type to support short-circuiting.

Short-Circuiting in the Handler Monad

In a web application, if we redirect to a different URL, we generally want the response to complete at that point. For example, if we have a request which requires an authenticated user, we might redirect them to a login page if they haven’t logged in, but if they’re already authenticated, we’d want the handler code to proceed. Another obvious short-circuiting case is when something goes wrong during execution and we want to immediately send an error response. If the monad doesn’t short-circuit, then the only alternative is to use nested if/else or case statements to control which code is executed 7.

You might also want the monad to short-circuit whenever you write the response content. In “real world” frameworks the behaviour varies so you need to know how each of them work 8.

So how do we make our monad short-circuit? One option is to add the EitherT monad transformer to our existing monad. If you’re not familiar with EitherT, the behaviour is analogous to the familiar Either type 9. If we call left (or equivalently throwError since EitherT is a MonadError instance), the monad will short-circuit 10.

data HandlerResult = Redirect ByteString     -- Redirect to a URL
                   | ResponseComplete        -- Send the response
                   | HandlerError ByteString -- Send an internal error response
                     deriving (Show, Eq)

type Handler a = EitherT HandlerResult (ReaderT RequestData (StateT ResponseState IO)) a

When we call runEitherT followed by runReaderT and runStateT, the result is of type IO (Either HandlerResult (), ResponseState).

The runHandler Function

As things stand now, we have a WAI Request object passed as an argument to the Application type. To process it, we lookup the handler in our Router and then:

  • Create a RequestData from the Request
  • Create an initial ResponseState
  • Run the hander to get back the Either HandlerExcept () result and the final ResponseState

The complete runHandler function looks like this:

import Network.Wai.Parse

runHandler :: Request -> Handler () -> IO Response
runHandler req h  = do
    (pParams, _) <- parseRequestBody lbsBackEnd req
    let initRes = ResponseState status200 [] ""
        rd = RequestData
              { waiReq      = req
              , queryParams = toMap $ fmap (\(n, v) -> (n, fromMaybe "" $ v)) $ queryString req
              , postParams  = toMap pParams
              }

    (result, res) <- runStateT (runReaderT (runEitherT h) rd) initRes
    let hdrs = resHeaders res
    return $ case result of
        Left ResponseComplete   -> responseLBS (resStatus res) hdrs (content res)
        Left (Redirect url)     -> responseLBS status302 ((hLocation, url) : hdrs) ""
        Left (HandlerError msg) -> responseLBS internalServerError500 hdrs (BL.fromStrict msg)
        Right _ -> error "Not handled"

toMap :: [(ByteString, ByteString)] -> Params
toMap = M.unionsWith (++) . map (\(x, y) -> M.singleton (TE.decodeUtf8 x) [TE.decodeUtf8 y])

The function parseRequestBody is part of the wai-extra library. It attempts to parse the request body as HTML Form data, returning a tuple containing a list of submitted parameters and a list of uploaded files. Since we aren’t supporting file uploads we ignore the second element of the tuple. If the request content-type is neither application/x-www-form-urlencoded nor multipart/form-data, then both these arrays will be empty and we need to read and parse the request body ourselves. We’ll look at this below.

Note that we’re taking the approach that all responses should short-circuit and assume it’s a programmer error if the handler doesn’t redirect, write a response or return an error message. This might be confusing if you’re used to the Left constructor of Either being the “error” case, but it’s really just the case that short-circuits 11.

Functions in the Handler Monad

The handler monad is not very useful by itself. We want to hide the details behind a convenient API for reading request properties and creating the response. We’ll look at some simple examples, but you can obviously write whatever functions best suit your needs.

Reading the request

When processing a request, we typically want to read parameters and/or the request body. Most frameworks do not differentiate between different types of request parameters, but let’s suppose we want to treat request body parameters separately from query string parameters 12. We’ll also assume that it’s an error to send duplicate values of the same parameter:

postParam :: Text -> Handler Text
postParam name = asks postParams >>= lookupParam name

queryParam :: Text -> Handler Text
queryParam name = asks queryParams >>= lookupParam name

lookupParam :: Text -> Params -> Handler Text
lookupParam name params = case M.lookup name params of
    Just [v] -> return v
    _        -> throwError $ HandlerError $ B.concat ["Missing or duplicate parameter", TE.encodeUtf8 name]

WAI’s Request record type has a field called requestBody which is of type IO ByteString. It produces the complete body a chunk at a time, returning an empty ByteString when the body is completely consumed. There’s also a convenience function to do this, which we can wrap to create our body function:

body :: Handler BL.ByteString
body = asks waiReq >>= liftIO . strictRequestBody

Note that the body can only be read once. It may already have been read by the function parseRequestBody which we used above and in that case, the body function would return an empty value 13.

Building the response

For the response, we’ll start by writing functions to:

  • redirect to another URL
  • set the status
  • set the content as text, JSON, HTML

The redirect function just takes a URL as a ByteString and short-circuits with the corresponding HandlerResult value:

redirect :: ByteString -> Handler a
redirect = throwError . Redirect

The runHandler function we wrote above does the rest of the work, setting the status code to 302 and the Location header to the supplied URL.

Setting the response status to a different value is easily done by changing the state:

status :: Status -> Handler ()
status s = modify $ \rs -> rs { resStatus = s }

and we can write the response content as text, JSON or (Blaze) HTML using the following functions:

import Data.Aeson
import Text.Blaze.Html (Html)
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)

text :: Text -> Handler ()
text t = setContentType "text/plain; charset=utf-8" >> (rawBytes . BL.fromStrict $ TE.encodeUtf8 t)

json :: ToJSON a => a -> Handler ()
json j = setContentType "application/json" >> rawBytes (encode j)

html :: Html -> Handler ()
html h = setContentType "text/html; charset=utf-8" >> rawBytes (renderHtml h)

rawBytes :: BL.ByteString -> Handler ()
rawBytes b = modify (\rs -> rs { content = b }) >> throwError ResponseComplete

setHeader :: HeaderName -> ByteString -> Handler ()
setHeader name value = modify $ \rs -> rs { resHeaders = (name, value) : resHeaders rs }

setContentType :: ByteString -> Handler ()
setContentType = setHeader "Content-Type"

Exception Handling

So far we’ve assumed that every Handler will produce a value of type Either HandlerResult (), but what happens if the code throws an exception instead? We can test this easily by just adding the following route to our myAppRouter above:

["eek"]  -> error "eek!"

Requesting the URL /eek from a browser returns the text response “Something went wrong” with a 500 response code. This is the default response produced by Warp’s internal error handler and it is easily customized 14. Alternatively we can catch the exception ourselves. We still need a function to convert our router into an Application, so we can do it there:

routerToApplication :: Router -> Application
routerToApplication route req respond =
  (runHandler req $ route pathInfo req)
    `catch` λ(e :: SomeException) -> return $ responseLBS internalServerError500 [] $ "Internal error"

Conclusion

Even though WAI is not really a standard web interface supported by multiple servers, it is common to multiple frameworks so an understanding WAI and Warp is useful if you are likely to be developing Haskell web applications.

In this article we’ve built a simple set of functions with which we can write web handlers which would look quite similar to those of a framework like Scotty, and you should now hopefully have a clearer idea of how they work. The full code can be downloaded here. For a more complex example, you can also see this kind of code in use in a project I’ve been working on which is an implementation of the OpenID Connect specification in Haskell 15. I’ll hopefully find time to write up more articles on this topic as the development proceeds.


  1. Warp doesn’t automatically limit the request size, for example, so someone can crash your application by sending a very large request. For example, you can use the curl command curl -v --data-urlencode 'username@my_giant_file.txt' localhost:3000/login to send a large file as a parameter. See also, Yesod’s maximumContentLength setting, which it uses to limit the request body size↩︎

  2. Scotty, Yesod, Hails, Apiary, Spock, Wheb, Simple. For a more complete list, you can look through Warp’s reverse dependencies↩︎

  3. For a good overview of WAI, see the Yesod Book↩︎

  4. The RWST monad transformer is another possibility and is used by the Spock Framework. In this case the “writer” part of the monad is ignored. ↩︎

  5. For an example which builds its own monad from scratch, see Apiary’s ActionT or Simple’s ControllerT↩︎

  6. You’ll see these extra request and response data options in Scotty’s ActionEnv and Content types, for example. ↩︎

  7. If we look at the type signatures for the redirect functions in existing frameworks, the handler monad is parameterized with an arbitrary type. In Scotty, for example, the type is redirect :: Text -> ActionM a so we can immediately deduce that redirect must short-circuit since it can’t return an arbitrary value. ↩︎

  8. Scotty doesn’t complete the response when you write the content using a function like text or json whereas Spock does. A list of Yesod handler functions which short-circuit can be found in the Routing and Handlers chapter of the Yesod book. ↩︎

  9. EitherT can be found in the either package and is also re-exported by the errors package. ↩︎

  10. You may notice that ExceptT is used in practice instead of EitherT. However, this requires version 2.2.1 or later of the mtl library, which in turn requires the use of transformers 0.4.*. GHC 7.8 comes with transformers 0.3 so you can end up with conflicting versions in your project if it depends on GHC and cabal will complain. EitherT does the same job, more or less, so we stick with that for now. ↩︎

  11. It’s also confusing that the naming conventions often reinforce this. For example, Scotty’s ActionError type deals with both redirects and errors. ↩︎

  12. For example, we might want to report an error if sensitive data like a password is sent in a URL. We couldn’t do this using Scotty’s param function, for instance. ↩︎

  13. Scotty reads the request body and stores it along with the other request data so that it can be accessed more than once. ↩︎

  14. The setOnExceptionResponse setting can be used for customization. The exception is caught and the response sent in the serveConnection function. The exception is then re-thrown to the fork function which calls the exception handler configured with setOnException and cleans up resources. ↩︎

  15. The project is also on github. It’s a work in progress but also includes session handling, for example. ↩︎