We are going to build a very simple bulletin board website using scotty and friends. It'll be so simple that we won't even use a database, but hopefully it'll provide enough information on scotty that you can continue it yourselves if you'd like.

You might also be interested in a version of this tutorial that uses twain instead.

But first, we are going to cover some of the basics of web programming and how to use scotty.

Scotty

Scotty is a server-side web framework, which means it provides a high-level API to describe web apps.

Scotty is built on top of WAI, which is a lower level web application interface, and warp, which is a web server implementation that runs wai apps (also called a WAI handler). A web server is a network application that receives requests from clients, processes them, and returns responses. The communication between the client and server follows the HTTP protocol. The HTTP protocol defines what kind of requests a user can make, such as "I want to GET this file", and what kind of responses the server can return, such as "404 Not Found".

wai provides a slightly low level mechanism of talking about requests and responses, and scotty provides a bit more convenient mechanism than WAI for that. Warp takes descriptions of web programs that are written using WAI and provides the actual networking functionality, including the concurrent processing.

If you are interested in working with wai directly, Michael Snoyman's video workshop Your First Web App with WAI and Warp is a good place to learn more about it.

How to Run

Scotty apps have the type ScottyM ().

Once we have a scotty app, we can:

  • Run it (using warp, in development mode) using the scotty function
  • Convert it to a WAI Application using scottyApp that can later be run with any WAI Handler, such as warp
  • Run it using warp while passing warp options with scottyOpts
  • Run scotty on a particular network socket with scottySocket
  • etc.

We will use scotty port myApp to run our scotty web application over the port in the variable port.

ScottyM

ScottyM (and more generally ScottyT) are types that describe scotty web apps. They describe how to process requests users make, and what kind of response should be sent to them.

Searching for ScottyM in the documentation for the Web.Scotty module For functions that return ScottyM () we can find a bunch of functions that resemble HTTP request methods:

  • get :: RoutePattern -> ActionM () -> ScottyM () - when the user wants to get data
  • post :: RoutePattern -> ActionM () -> ScottyM () - when the user wants to submit data
  • ...

Each such function take two arguments: RoutePattern and ActionM (), and return ScottyM ().

The name of the function represents the type of method we expect to handle, the RoutePattern argument represents the http path pattern to handle, and the ActionM () argument represents what to do when receiving a request of this shape.

For example: get (literal "/") (text "Hello!") is a description of a scotty web app that when it receives the HTTP request GET / it will return the text "Hello".

Both ScottyM and ScottyT implement the Monad interface (and ScottyT is a monad transformer if you're interested in that) so they can be combined with other ScottyMs and ScottyTs respectively. So:

do
  get (literal "/hello") (text "Hello!")
  get (literal "/world") (text "World!")

Will try to check if the user request matches the first pattern (GET /hello), and if it doesn't, it will try to match the second pattern (GET /world). If all patterns fail scotty will use a default action to say "Not found".

We'll describe what kind of routes we can describe and what kind of actions we can do next.

Routes

Scotty provides several ways to describe routes using static paths, variable capture, regex and more. The various functions to describe a route can be found in the module documentation.

Another way to describe routes is using the ghc extension OverloadedStrings, so writing simply "/hello" is the same as writing (capture "/hello").

When writing routes, we sometimes want to describe more than just a static path, sometimes we want part of the path to vary. For that we can use capture. To capture part of the path, prefix a name with a colon (:), like this:

capture "/post/:id" will match /post/17, /post/123, /post/hello and more. And later in the ActionM part, we can use the function param to get the part of the route with the matching name like this: param "id".

Check out the various ways to create route patterns in the module documentation.

For our bulletin board we want to create several routes:

get "/" -- Our main page, which will display all of the bulletins
get "/post/:id" -- A page for a specific post
get "/new" -- A page for creating a new post
post "/new" -- A request to submit a new page
post "/post/:id/delete" -- A request to delete a specific post

next, we'll define what to do if we match on each of these routes.

ActionM

Once we match an http method and route, we can decide what to do with it. The type that represents that is ActionM (and more generally, ActionT).

ActionM and ActionT also implement the monad interface, so we can chain them the way we are used to from types like IO, the will run one action after the other.

In ActionM context, we can find out more details about the request, do IO, decide how to respond to the user, and more.

Querying the Request

The request the user sent often holds more information than just the http method and route. It can hold request headers such as which type of content the user is expecting to get or the "user-agent", in case of the http methods such as POST and PUT it can include a body which includes the actual content, and more.

Scotty provides a simple way to query a few of the more common parts of a request, with functions such as body, header and files. It also provides the entire request if needed.

It also provides easy access to the varying parts of the route that we "captured", with param and params.

For our case this will come into play when we want to know which post to refer to (what's the id in the path is), and what the content of the post is (in the /new route).

Responding to the user

There are several ways to respond to the user, the most common ones is to return some kind of data. This can be text, html, json, a file or more. In http, in addition to sending the data, we also need to describe what kind of data that is and even that the action is successful at all. Scotty handles all that for the common cases by providing functions such as text, html, and json.

So for example, if we want to send a simple html page on the route /hello, we'll write:

get "/hello" (html "<html><head><link rel=\"stylesheet\" type=\"text/css\" href=\"/style.css\"></head><body>Hello!</body></html>")

For other cases, for example sending css styling data, we will need to signal that this is what we're sending ourselves. To do that we set the response headers.

So for example, if we wanted to return css on the route /style.css, we'll write:

get "/style.css" $ do
  setHeader "Content-Type" "text/css; charset=utf-8"
  raw "body { width: 900px; margin: auto; }"

Visit the module documentation for more information about response headers and response bodies.

Exceptions and Control Flow

It is possible to throw errors to stop current the current ActionM, and it's possible to move to the next route handler as well.

I won't talk much about error handling and control flow between route handlers, but it's worth knowning it exists when you need it.

IO

It is possible to use IO operations both in ScottyM and in ActionM context using the function liftIO. For example:

get "/hello" $ do
  liftIO (putStrLn "They said hello!")
  text "Hello back!"

This way we can write to console, change a song in our music player, or query a database in the middle of processing a request! Fair warning though: Warp runs request processing concurrently, so make sure you avoid race conditions in your code!

Alright, enough chitchat - let's get to work

We now have the basic building block with which we can build our bulletin board. There are a few more things we can cover that will make our lives easier, but we'll pick them up as we go.

At the time of writing the most recent scotty version is 0.12. Make sure you add that to your cabal file!

Some simple structure

{-# language OverloadedStrings #-}

import qualified Web.Scotty as S

main :: IO ()
main = do
  S.scotty 3000 myApp

myApp :: S.ScottyM ()
myApp = do
  -- Our main page, which will display all of the bulletins
  S.get "/" $
    S.text "not yet implemented"

  -- A page for a specific post
  S.get "/post/:id" $
    error "not yet implemented"

  -- A page for creating a new post
  S.get "/new" $
    error "not yet implemented"

  -- A request to submit a new page
  S.post "/new" $
    error "not yet implemented"

  -- A request to delete a specific post
  S.post "/post/:id/delete" $
    error "not yet implemented"

We'll start with a very simple routing skeleton. For the sake of simplicity, I'm going to put this code in main.hs and run it using:

stack runghc --package scotty main.hs

Eventually the program will greet us with the following output:

Setting phasers to stun... (port 3000) (ctrl-c to quit)

Which means that we can now open firefox a go to http://localhost:3000 and be greeted by our scotty application.

Displaying posts

Next, we are going to need figure out how to represent our bulletin data and how to keep state around.

We are going to add a few new packages to use for our data representation: text, time, containers and http-types.

Add above:

import qualified Data.Text.Lazy as TL
import qualified Data.Time.Clock as C
import qualified Data.Map as M
import qualified Network.HTTP.Types as HTTP

And we'll represent a post in the following way:

data Post
  = Post
    { pTime :: C.UTCTime
    , pAuthor :: TL.Text
    , pTitle :: TL.Text
    , pContent :: TL.Text
    }

And we'll use a Map to represent all of the posts:

type Posts = M.Map Integer Post

Once we have these types, we can thread a value of type Posts to myApp, so they will be available to all requests and responses handlers. We'll change main and myApp a bit and add some dummy data.

main :: IO ()
main = do
  dummyPosts <- makeDummyPosts
  S.scotty 3000 (myApp dummyPosts)

myApp :: Posts -> S.ScottyM ()
myApp posts = do
  -- Our main page, which will display all of the bulletins
  S.get "/" $
    S.text $ TL.unlines $ map ppPost $ M.elems posts

  -- A page for a specific post
  S.get "/post/:id" $ do
    pid <- S.param "id"
    case M.lookup pid posts of
      Just post ->
        S.text $ ppPost post

      Nothing -> do
        S.status HTTP.notFound404
        S.text "404 Not Found."

  -- A page for creating a new post
  S.get "/new" $
    error "not yet implemented"

  -- A request to submit a new page
  S.post "/new" $
    error "not yet implemented"

  -- A request to delete a specific post
  S.post "/post/:id/delete" $
    error "not yet implemented"


makeDummyPosts :: IO Posts
makeDummyPosts = do
  time <- C.getCurrentTime
  pure $
    M.singleton
      0
      ( Post
        { pTime = time
        , pTitle = "Dummy title"
        , pAuthor = "Dummy author"
        , pContent = "bla bla bla..."
        }
      )

ppPost :: Post -> TL.Text
ppPost post =
  let
    header =
      TL.unwords
        [ "[" <> TL.pack (show (pTime post)) <> "]"
        , pTitle post
        , "by"
        , pAuthor post
        ]
    seperator =
      TL.replicate (TL.length header) "-"
  in
    TL.unlines
      [ seperator
      , header
      , seperator
      , pContent post
      , seperator
      ]

Now, when running our program with:

stack runghc --package scotty --package text --package containers --package http-types main.hs

We should be able to see a post when going to, http://localhost:3000 see the same post when going to http://localhost:3000/post/0 and see a not found message when trying to go to a post with a different id such as http://localhost:3000/post/17

Managing mutable state

Now while this is good we are still missing a few parts:

  • Adding new posts
  • Generating new distinct post ids on post creation
  • Making sure all threads access the same state without stepping on each other's toes

While we could use a mutable variable like IORef or MVar, writing code that can run a sequence of commands that use mutable data can be tricky.

For example one thing we want to do, when creating a new post is:

  1. Get the current id
  2. Increment it, use that id to create a new post
  3. update the mutable variable to point to the new map

However, if, for example, two threads manage to get the same id before incrementing the id, we'll get two posts with the same id. Or if two threads create the new map and ask the mutable variable to point at their new map, one post will be not actually be added and will be lost forever.

To combat that, we'll use shared memory using Software Transactional Memory (STM). the stm packages provides us with mutable variables that can be shared and updated concurrently in an atomic way. Meaning that we can describe a sequence of operations on shared memory that are guaranteed to run atomically as one transaction without other operations on the same mutable variables getting mixed in between.

I recommend reading the chapter of STM in PCPH to get a more in-depth overview of stm.

Now - we can create a state data type which contains the posts currently existing in the system as well as an updating id for the next post added to the system:

data MyState
  = MyState
    { msId :: Integer
    , msPosts :: Posts
    }

And then wrap it up in a transaction mutable variable: STM.TVar MyState.

We can create a new TVar in an IO context and pass it to myApp so that the scotty web app is a closure containing the mutable variable, and that way any thread handling requests and responses will have access to it!

We'll add a new import:

import qualified Control.Concurrent.STM as STM

And we'll edit our main and myApp now to:

main :: IO ()
main = do
  posts <- makeDummyPosts
  mystateVar <- STM.newTVarIO MyState{msId = 1, msPosts = posts}
  S.scotty 3000 (myApp mystateVar)

myApp :: STM.TVar MyState -> S.ScottyM ()
myApp mystateVar = do
  ...

The three most interesting functions we have (for now) to operate on our mutable transactional variable mystateVar are:

readTVar   :: TVar a -> STM a
writeTVar  :: TVar a -> a -> STM ()

atomically :: STM a -> IO a

the STM type we see here is similar to IO, it is a description of a transactional program, a sequence of steps that must run atomically. And the atomically function is one that converts that program into something that the haskell runtime system can run.

So now, creating a new post and adding it to the current state of the system looks like this:

newPost :: Post -> STM.TVar MyState -> IO Integer
newPost post mystateVar = do
  STM.atomically $ do
    mystate <- STM.readTVar mystateVar
    STM.writeTVar
      mystateVar
      ( mystate
        { msId = msId mystate + 1
        , msPosts = M.insert (msId mystate) post (msPosts mystate)
        }
      )
    pure (msId mystate)

And these operations are guaranteed to run atomically. We can also use STM.modifyTVar :: TVar a -> (a -> a) -> STM () for a slightly more convenient code.

Let's add another import so we can run IO actions inside ActionM:

import Control.Monad.IO.Class (liftIO)

Lets change the code of myApp to handle viewing and deleting posts:

myApp :: STM.TVar MyState -> S.ScottyM ()
myApp mystateVar = do
  -- Our main page, which will display all of the bulletins
  S.get "/" $ do
    posts <- liftIO $ msPosts <$> STM.readTVarIO mystateVar
    S.text $ TL.unlines $ map ppPost $ M.elems posts

  -- A page for a specific post
  S.get "/post/:id" $ do
    pid <- S.param "id"
    posts <- liftIO $ msPosts <$> STM.readTVarIO mystateVar
    case M.lookup pid posts of
      Just post ->
        S.text $ ppPost post

      Nothing -> do
        S.status HTTP.notFound404
        S.text "404 Not Found."

  -- A page for creating a new post
  S.get "/new" $
    error "not yet implemented"

  -- A request to submit a new page
  S.post "/new" $
    error "not yet implemented"

  -- A request to delete a specific post
  S.post "/post/:id/delete" $ do
    pid <- S.param "id"
    exists <- liftIO $ STM.atomically $ do
      mystate <- STM.readTVar mystateVar
      case M.lookup pid (msPosts mystate) of
        Just{} -> do
          STM.writeTVar
            mystateVar
            ( mystate
              { msPosts = M.delete pid (msPosts mystate)
              }
            )
          pure True

        Nothing ->
          pure False
    if exists
      then
        S.redirect "/"

      else do
        S.status HTTP.notFound404
        S.text "404 Not Found."

We can test both GET and POST requests from the command line using curl:

To see all posts:

curl -X GET http://localhost:3000

To see the post with id 0:

curl -X GET http://localhost:3000/post/0

To delete the post with id 0:

curl -X POST http://localhost:3000/post/0/delete

HTML and forms

We're going to start writing some HTML to display our data and add a form for adding a new post.

We're going to use lucid. If you are interested in more possible choices for html libraries vrom911's article about html libraries is a good place to start.

Lucid provides a monadic EDSL for writing html pages. The functions are all suffixed with underscore (_) and represent the relevant html tags.

We'll add this import at the top:

import qualified Lucid as H

And the following type:

type Html = H.Html ()

And first, we'll create a template boilerplate which into we'll inject our content later:

template :: TL.Text -> Html -> Html
template title content =
  H.doctypehtml_ $ do
    H.head_ $ do
      H.meta_ [ H.charset_ "utf-8" ]
      H.title_ (H.toHtml title)
      H.link_ [ H.rel_ "stylesheet", H.type_ "text/css", H.href_ "/style.css"  ]
    H.body_ $ do
      H.div_ [ H.class_ "main" ] $ do
        H.h1_ [ H.class_ "logo" ] $
          H.a_ [H.href_ "/"] "Bulletin Board"
        content

Notice how the lists represent the attributes of a tag, how tags are sequenced using the monadic interface, and how tags are nested by passing them as input to other tags.

Let's create pages for posts:

postsHtml :: Posts -> Html
postsHtml posts = do
  H.p_ [ H.class_ "new-button" ] $
    H.a_ [H.href_ "/new"] "New Post"
  mapM_ (uncurry postHtml) $ reverse $ M.toList posts

postHtml :: Integer -> Post -> Html
postHtml pid post = do
  H.div_ [ H.class_ "post" ] $ do
    H.div_ [ H.class_ "post-header" ] $ do
      H.h2_ [ H.class_ "post-title" ] $
        H.a_
          [H.href_ (TL.toStrict $ "/post/" <> TL.pack (show pid))]
          (H.toHtml $ pTitle post)

      H.span_ $ do
        H.p_ [ H.class_ "post-time" ] $ H.toHtml (TL.pack (show (pTime post)))
        H.p_ [ H.class_ "post-author" ] $ H.toHtml (pAuthor post)

    H.div_ [H.class_ "post-content"] $ do
      H.toHtml (pContent post)

And change our web handlers to use html instead of text:

  -- Our main page, which will display all of the bulletins
  S.get "/" $ do
    posts <- liftIO $ msPosts <$> STM.readTVarIO mystateVar
    S.html $
      H.renderText $
        template
          "Bulletin board - posts"
          (postsHtml posts)

  -- A page for a specific post
  S.get "/post/:id" $ do
    pid <- S.param "id"
    posts <- liftIO $ msPosts <$> STM.readTVarIO mystateVar
    case M.lookup pid posts of
      Just post ->
        S.html $
          H.renderText $
            template
              ("Bulletin board - post " <> TL.pack (show pid))
              (postHtml pid post)

      Nothing -> do
        S.status HTTP.notFound404
        S.html $
          H.renderText $
            template
              ("Bulletin board - post " <> TL.pack (show pid) <> " not found.")
              "404 Post not found."

In order to delete a post, we need to make a POST command to the URL /post/<post-id>/delete. We can do that using html by creating a form, defining its URL and method, and create an input html element of type submit.

    H.form_
      [ H.method_ "post"
      , H.action_ (TL.toStrict $ "/post/" <> TL.pack (show pid) <> "/delete")
      , H.onsubmit_ "return confirm('Are you sure?')"
      , H.class_ "delete-post"
      ]
      ( do
        H.input_ [H.type_ "submit", H.value_ "Delete", H.class_ "deletebtn"]
      )

You can stick this wherever you want in postHtml, I placed it at the end. Now, if you run the program using:

stack runghc --package scotty --package text --package containers --package stm --package http-types --package lucid main.hs

and go to the website (http://localhost:3000), you'll be greeted with beautiful (well, not beautiful, but functional) posts and a delete button for each post.

Submitting data via forms and processing it

Next we are going to add a post. To do that we need to create a new html page which will contain another html form. This time we will want to capture some input which will then be part of the body of the POST request.

newPostHtml :: Html
newPostHtml = do
  H.form_
    [ H.method_ "post"
    , H.action_ "/new"
    , H.class_ "new-post"
    ]
    ( do
      H.p_ $ H.input_ [H.type_ "text", H.name_ "title", H.placeholder_ "Title..."]
      H.p_ $ H.input_ [H.type_ "text", H.name_ "author", H.placeholder_ "Author..."]
      H.p_ $ H.textarea_ [H.name_ "content", H.placeholder_ "Content..."] ""
      H.p_ $ H.input_ [H.type_ "submit", H.value_ "Submit", H.class_ "submit-button"]
    )

And we need to be able to access the following from the request on the server. We can do that using param. So let's change myApp to include:

  -- A page for creating a new post
  S.get "/new" $
    S.html $
      H.renderText $
        template
          ("Bulletin board - add new post")
          newPostHtml

  -- A request to submit a new page
  S.post "/new" $ do
    title <- S.param "title"
    author <- S.param "author"
    content <- S.param "content"
    time <- liftIO C.getCurrentTime
    pid <- liftIO $ newPost
      ( Post
        { pTime = time
        , pAuthor = author
        , pTitle = title
        , pContent = content
        }
      )
      mystateVar
    S.redirect ("/post/" <> TL.pack (show pid))

And now we have a fairly functional little bulletin board! Hooray!

Styling

This post is already pretty long, so I will not cover styling in depth.

There are multiple way to use styling:

The first is using the EDSL approach like we did with lucid using a library like clay, the second is to write the css text inline in a Haskell module using something like the raw-strings-qq library, another is to write it in an external file and embed to context at compile time using template haskell and the file-embed library, another is to ship the css file along with the executable and use file from scotty to send it as a file.

For each of these - don't forget to set the content type header to "text/css; charset=utf-8"!

Logging, Sessions, Cookies, Authentication, etc.

The wai ecosystem has a wide variety of features that can be composed together. These features are usually encapsulated as components called "middlewares". Middlewares can add functionality before the request passes to our scotty app or after the response.

The wai-extra packages contains a bunch of middlewares we can use. Like gzip compression of responses, forcing ssl usage, or simple http authentication.

To add middlewares to scotty apps, place them at the top of the routing commands order and use the middleware command to embed them into the scotty app.

More functionality exists outside of wai-extra, the scotty examples directory on Github constains a bunch of examples of using different middlewares such as cookies, logging, and more.

Deploying

I usually create a static executable using ghc-musl and docker so I can deploy my executable on other linux servers.

In a stack project, add the following sections:

Add this to the stack.yaml:

docker:
  enable: true
  image: utdemir/ghc-musl:v22-ghc8107

and this to the .cabal file under the executable section:

  ghc-options: -static -optl-static -optl-pthread -fPIC -threaded -rtsopts -with-rtsopts=-N

Check the ghc-musl repo for more instructions.

That's it

I hope you found this tutorial useful. If there's something you feel I did not explain well or you'd like me to cover, let me know via email, mastodon, or discourse.

The whole program including the stack and cabal files can be found on Github.

And if you'd like to see a more featureful example of building a website with scotty, see my next post A bulletin board website using Haskell, scotty and friends.