Prologue

About the book

Part of a Read You A _™ series. © 2017 Guru Devanla

Scotty is a relatively light-weight and interesting Haskell library that can be used to inform novice Haskeller’s on how Haskell is used in the real world. It provides the next level of reading to learn Haskell by exploring the use of the powerful data structures Haskell provides. The purpose of this book is to educate the reader beyond just learning the basics of programming in Haskell. Many other books currently available cover Haskell as a language at various depths. This book follows the same spirit as the popular Real World Haskell(RWH) book. The RWH teaches the language and its use in real world scenarios. This mini-book takes a deeper dive into one specific library and exposes the reader to ways in which the various data structures in Haskell are put to use.

The main objective of this book are as follows:

  1. Expose the reader to practical examples of use of Monads, Monad Transformers other power structures Haskell provides. Scotty library uses all the important monads(State, Maybe, Reader) taught in beginner Haskell books

  2. Looks at how these computation structures are organized in a purely functional manner

  3. Educate the reader, so that they can contribute to Scotty or build similar powerful libraries

At the minimum, after reading this book, the reader should be able to reason with any code that is implemented using Scotty as the web framework.

This book assumes basic familiarity of the reader with Haskell concepts. Some of the advanced data structures that will be used in the later parts of the book are introduced in the first chapter in a gradual manner. But, this introduction does not provide detailed explanations to concepts that are available in other general books on Haskell.

How to read this book

This book obviously uses extensive references to the Scotty source code. Appropriate links are provided to the source code from the sections where the code is discussed. It could be beneficial to clone the scotty library from its original source locally and explore the code as the book is read.

If you desire a stack enabled version, and the version the book links the source code to, you can fork a version from scotty-forked. This version is forked so as to be able to refer to a consistent version of the library from different sections in this book and also can be built using stack.

Also, refer to the References section to refer to resources I used in helping me understand the implementation. These resources can provide the missing pieces not covered in this book.

Introduction

This chapter gives an overview of the approach taken in this book to help the reader read through the Scotty implementation. As stated, in the Prologue this book is intended to help familiarize ourselves with Haskell’s use in real-world. Therefore, the book will assume basic knowledge in Haskell (acquired from books like LYH, Haskell from First Principles etc).

One could go about reading an existing implementation in two ways. One approach is to delve in right away and start looking through the code until we reach a logical starting point from where we can anchor our understanding. From the logical point we could traverse the code in different directions to enhance our understanding of the code. Typically, we could take this approach if we find ourselves in a situation where we want to learn the code by fixing a particular bug or working on a new feature request.

Alternatively, we could sit back (if we have the time), and think about the different ways of solving the problem at hand. Then, with that idea, if we were to look at the existing implementation, the process we went through could inform us on why the code has been implemented the way it is.

For our purposes, to understand the Scotty implementation we will take the latter approach. As a first step, we will create our own toy implementation of the Scotty like framework. While we do this we will reason about the limitations of our code during each iteration and then improve on that. After a few iterations we will be at a point, where our code will closely represent the overall design of the original Scotty implementation. This exercise will both, make it easy to read through the original implementation and also provide a way of reasoning about the design decisions reflected in the code.

Once we have our toy implementation in place, we start off by looking at a simple web application built using Scotty. That will help us define some terminology that we can use across the book. Some of this terminology is also introduced while we implement our toy framework.

We then turn our attention to a simple type Options that will introduce us to the (Types.hs. The Types.hs module contains all the type definitions used by the Scotty library.

One of the first things we need to do while defining a web application is to map the different HTTP requests to methods that act on those requests. We need a way to thread the requests through different actions that serve request. We call this process routing. Therefore, next we look at how this routing pipeline is created by Scotty.

Once the routing pipeline is created, then we can look at how the user requests are threaded through these actions. This will give us insight on how the scotty state is unwrapped before each request and how the requests are passed on to the appropriate action.

Next, we look closely at a routing function in detail. The routing function threads each request through an action by matching an url pattern. We will also come across the ActionT monad that wraps an environment (HTTP request information), the response and any error values that may have been created.

By now we would have looked at most of the core Scotty implementation. We will continue to explore the other parts of library , namely parameter handling and Response creation and handling.

A Toy Scotty

In this section we will build a simple framework. This framework will allow us to creates route handlers that will represent the various routes in a web app, provide default routes and also handle errors. We will start with the simplest of setups and slowly work our way towards a model that closely represents the design that is used in Scotty. The hope is this step by step approach to a relatively Scotty like model will help the reader understand the Scotty code better when we start exploring the code in the later chapters.

Each iteration in this chapter is contained in one independent module. Each module contains both the server code that will serve requests and client code that will simulate any handlers the client(user of our framework) provides. The client usually provides the route handlers that contain the custom logic to handle requests. The server code does the job of calling this handlers to process request before sending back the response.

All the code examples discussed in this section is available at scotty-from-ground-up.

The code can be compiled using stack. To run the example, in the first iteration of this chapter follows these steps.


stack build

stack exec main1

Each module can be run as stack exec mainX , where X is the number of the iteration. For example, the command to run the code in the first iteration would be stack exec main1.

First Iteration

The code discussed in this iteration is available at Main1.hs.

Our first task is to declare some of the data types we will need.

import qualified Control.Monad.Trans.State.Strict as ST
import Data.List
import Control.Monad

type Route = String -> String

data AppState = AppState { routes::[Route]}

type AppStateT = ST.State AppState

The Route type will be a set of routing functions the client can add to handle different requests. We will have to capture the list of routes provided by the client. We do that by wrapping the Route type in AppState. Since, we will be creating the list of Routes during runtime we wrap our AppState in a State monad. We will update this state monad as a first step when the application is run.

As part of the framework methods, we want the user to be able to declare all the routes that need to be checked to handle any request. We let the user invoke myScotty with the function that declares all the routes of the app. Our first iteration of the framework functions will look as follows:

--  framework methods

addRoute' :: Route -> AppState -> AppState
addRoute' mf s@AppState {routes = mw} = s {routes = mf:mw}

addRoute mf = ST.modify $ \s -> addRoute' mf s

runMyApp :: Monad m => String -> ST.State AppState a -> m String
runMyApp initial_string my_app = do
  let s = ST.execState my_app AppState{ routes = []}
  let output = foldl (flip ($)) initial_string (routes s)
  return $ output

myScotty my_app = do
  putStrLn "Please type in the request"
  putStrLn "(one of 'handler1', 'handler2', 'handler3', 'buggy' or any string for default handling)"
  request <- getLine
  unless (request == "q") $ do
    let response = runMyApp request myApp
    case response of
      Just x -> putStrLn x
      Nothing -> putStrLn "Error"
    main

Here, the client will invoke ‘myScotty` with a function that returns `AppStateT ()’. An example implementation of route handlers that uses the simple framework will be

-- client functions
constructResponse :: [String] -> String
constructResponse = unwords

routeHandler1 :: String -> String
routeHandler1 request =
  constructResponse [
  "\nrequest in handler1: got " ++ request]

routeHandler2 :: String -> String
routeHandler2 request = constructResponse [
      "\n\trequest in handler2 got :" ++ request]

routeHandler3 :: String -> String
routeHandler3 request = constructResponse [
  "\n\t\trequest in handler3:" ++ request]

myApp :: AppStateT ()
myApp = do
  addRoute routeHandler1
  addRoute routeHandler2
  addRoute routeHandler3

Here as a client of the framework we will create three functions routeHandlerX functions that will be the handlers for processing a respective requests. We will add these route handlers using the addRoute method in myApp. The myApp will be the argument to myScotty function provided by the framework.

Finally, our main will be

main :: IO ()
main = myScotty myApp

Here we call myScotty and provide the list of handlers that can be used to process requests.

Now let us look closely at what is happening in our toy framework methods. You can ignore what is happening in main for now. In the main function we just loop around and wait for user input to be processed. The functions of interest to us would be addRoute

addRoute' :: Route -> AppState -> AppState
addRoute' mf s@AppState {routes = mw} = s {routes = mf:mw}

addRoute mf = ST.modify $ \s -> addRoute' mf s

runMyApp :: Monad m => String -> AppState -> m String
runMyApp initial_string my_app = do
  let output = foldl (flip ($)) initial_string (routes my_app)
  return $ output

myScotty my_app = do
  let app_state = ST.execState my_app AppState{routes=[]}
  userInputLoop app_state

The main function, applies myScotty to myApp. The myScotty function first sets up the state of AppState. The app_state values has the list of router handlers that were declared in myApp. When myApp is evaluated, each expression in myApp calls addRoute which modifies the state of AppState. Therefore, in myScotty when we execState, the AppState objects has all the routes stored in the routes attribute.

After we execState and set up the state of AppState, we are ready to run a loop (that simulates a server) and start handling user requests. In userInputLoop, after accepting the input string from the user, we apply runMyApp to the user input and pass along our AppState value that has all the routes stored in it. The runMyApp function folds over the list of routes and applies each route to the previous request string passed to it.

userInputLoop app_state = do
  putStrLn "Please type in the request"
  putStrLn "(one of 'handler1', 'handler2', 'handler3', 'buggy' or any string for default handling)"
  request <- getLine

  unless (request == "q") $ do
    let response = runMyApp request app_state
    case response of
      Just x -> putStrLn x
      Nothing -> putStrLn "Error"
    main

Let’s run the module and provide some input at the prompt.

stack build

stack exec main1

You will notice, that this is not how we want apply routes to a user request. We only want the user request processed by one route. But, hang on. We do this to help us build towards what we ultimately need.

Second Iteration

We notice that in the first iteration our code did not do a good job of processing requests only with one handler. We will fix that in this iteration. To fix that, we need each routeHandler to specify a condition on which it should be called to process the request. The code for the second iteration is available at Main2.hs.

First we introduce a few more type synonyms to help us in the process. We do this so that we can structure computation in such a way that if one route fails to process the request (since the request does not meet the condition) we want to be able to chain our call to the next router. This will become clear when we review the route function. Also, keep in mind that some of the design decisions we make here are tuned to get us to a toy framework that closely resembles the structure in the actual implementation of Scotty.

type Application = String -> String
type Route = Application -> Application

We will talk more on this type when we discuss the route function. We make a change to the addRoute function where instead of calling addRoute' directly, we call a function called route. This is where the interesting stuff happens in this iteration.

Let’s take a look at the route method.

route :: Application -> (String -> Bool)
  -> Route
route mw pat mw1 input_string =
  let tryNext = mw1 input_string in
  if pat input_string
  then
    mw input_string
  else
    tryNext

The route method takes an handler function which is of type Application or String->String. This type is the routeHandler the client provides. The route method captures the routeHandlers in its closure. We call these routeHandlers the action. The second parameter to this function is the predicate that needs to be True for this action to be called. When the call to route from addRoute returns, we have a function of type Route. But, what is this Route

Route

reduces to

(Application) -> (Application)

reduces to

(String -> String) -> String -> String

Therefore, what gets added to the routes attribute is a function (that has the action or routeHandler in its closure), and takes another Application as a parameter along with the String which will be our Request.

The route function, calls the enclosed routeHandler if the predicate is satisfied, else the call is chained to the next Application. We can see this action unfold in the foldl operation used in runMyApp.

runMyApp def app_state request = do
  let output = foldl (flip ($)) def (routes app_state) request
  return output

The def here is the defaultRoute handler. You notice that as this function folds the each value is routes is called with the next value in routes and the request string. Please take a moment to understand this. The core part of Scotty happens around this function, where the processing of actions are setup. You should try to list the values of routes as they get created and then fold over those values and see how the type checks out. As a new user to Haskell this is an interesting pattern I came across. The types checkout as the recursive nature of calls unfold. The tryNext function is called recursively until a particular predicate is met or else in the end the default route handler is called.

The client functions remain the same, except we change the response and also align the types to the new Application type.

Try running this example with suggested input and then with some random input.

Third iteration

In the third iteration, we switch the return type of route handlers. We will update the route handlers to return a Maybe value. That way, if the value returned is Nothing a default error handler can be invoked later on.

For this we do a couple of changes to the code from the second iteration. The full code for this iteration is available at Main3.hs.

We first update the type variable Application to return a Maybe value rather than a String. For clarity we also introduce two other type synonyms, namely, Request and Response

type Response = Maybe String
type Request = String

type Application = Request -> Response

Then we add a default error handler that will be invoked if any of the routeHandler return a Nothing value.

errorHandler :: Request -> Response
errorHandler request = Just $ constructResponse [
  request, "Nothing returned from one of the handlers"]

We then update the route method from second iteration to handle the Maybe return values. Notice that if a routeHandler was invoked and if the returned Response from the routeHandler was a Nothing value, then the errorHandler is invoked.

We also update the types of all the framework function to reflect the change of the response type from String to Maybe String.

Now, on the client side, we update all of routeHandlers to return a Maybe value as a Response. To show how our change works, the routeHandler2 has been updated to return Nothing.

routeHandler1 :: Request -> Response
routeHandler1 request =
  Just $ constructResponse [
  "request in handler1: got " ++ request]

routeHandler2 :: t -> Maybe a
routeHandler2 request = Nothing

routeHandler3 :: Request -> Response
routeHandler3 request =
  Just $ constructResponse [
  "request in handler3:" ++ request]

defaultRoute :: Request -> Response
defaultRoute request =
  Just $ constructResponse [
  request , "processed by defaultRoute"]

Try running the program,

stack build
stack exec main3

When the request string passed to the program is handler2, then the routeHandler2 is called with the request string. Since, routeHandler2 returns a Nothing value, the errorHandler is called and no other routeHandlers is invoked from this point for this Request.

$ stack exec main3
Please type in the request
(one of 'handler1', 'handler2', 'handler3', 'buggy' or any string for
default handling)
handler2
Request=handler2, Response=Nothing returned from one of the handlers

You will notice that even though we were able to handle Nothing values returned from some routeHandlers, we still do not handle any exceptions that could be thrown from the routeHandlers. We will be taking care of that in later iterations of this code. Also, as is the case with returning Nothing values, the nature of error is not available. We could benefit from more information in cases where routeHandlers cannot process a Request successfully.

Fourth Iteration

In this iteration of code we would like to handle any exceptions thrown from any of the routeHandlers. The full code for this iteration is available at Main4.hs.

To get the error handling we need, we go back to our types and refine them further. The new type definitions we will need in this iteration are as follows

type Response = String
type Request = String

-- new in this iteration
type ActionError = String
type ActionT = Exc.ExceptT ActionError Maybe Response
type Application = Request -> ActionT

type Route = Application -> Application

data AppState = AppState { routes:: [Route]}
type AppStateT = ST.State AppState

Almost all types definitions you see above are carried over from the previous iteration. The important changes are to the Application type and by dependency to the Route type.

We define an ActionError type, that will hold an exception string that the routeHandlers can create. Therefore, we need to be able to wrap the ActionError along with the Maybe Response value we expect from the routeHandler functions.

We reach out to the ExceptT monad for that. The ExceptT monad wraps the Either e a in an outer monad. We pick this monad transformer, since in the later sections we will see that we have a need to stack more monads to get to what we want. Therefore, for this iteration each routeHandler will either throw an exception which is captured in ActionError or return a Maybe value which is captured in Maybe Response. Note that we could have gotten away with an Either e a monad for this iteration. The type could have been Either ActionError Request. But, we skip that step and directly reach out to ExcepT for reasons that become clearer later.

Now, we will see how we can handle these exceptions. Similar to our previous iterations, we will update all our routeHandlers to reflect the new types. The routeHandlerBuggy will throw an exception whereas all other routeHandlers successfully process requests. The new listing of routeHandlers is shown below.

constructResponse = unwords

routeHandler1 :: Request -> ActionT
routeHandler1 request =
  Exc.ExceptT $ Just $ Right $ constructResponse [
  "request in handler1: got " ++ request]

routeHandler2 :: Request -> ActionT
routeHandler2 input = Exc.ExceptT $ Just $ Right $ input ++ " middleware2 called\n"

routeHandlerBuggy :: Request -> ActionT
routeHandlerBuggy input = throwError "Error from routeHandlerBuggy"

routeHandler3 :: String -> ActionT
routeHandler3 request =
  Exc.ExceptT $ Just $ Right $ constructResponse [
  "request in handler3:" ++ request]

defaultRoute :: Request -> ActionT
defaultRoute request =
  Exc.ExceptT $ Just $ Right $ constructResponse [
  request , "processed by defaultRoute"]

In each of the routeHandlers we construct the response and then wrap them into Either and then into a Maybe type. The wrapping of Maybe at this point may not add much value, since a Right value would indicate error anyways. But, as stated before the use of the transformer becomes essential for the later steps.

Now with the knowledge of how we expect our client to provide the routerHandlers,we turn our attention to the framework functions. First, we provide a errorHandler function which will be invoked from the catch block. This function will be called in the event of any exception that is thrown from the routeHandlers.

errorHandler :: Request -> ActionT
errorHandler s = Exc.ExceptT $ Just $ Right $ "There was an error returned: " ++ s

Then, we update our route function to catch exceptions. Note, that we updated the call to errorHandler in third iteration. Instead of checking for Nothing values before calling the errorHandler (in third iteration), we call cathcError and provide the errorHandler as the second argument to the catchError. We abstract away this into another function called runAction.

route ::(Request -> ActionT) -> (String -> Bool) -> Route
route mw pat mw1 request =
  let tryNext = mw1 request in
  if pat request then
    runAction mw request
  else
    tryNext

runAction ::(Request -> ActionT) -> Request -> Response
runAction mw request =
  let response = Exc.runExcept $ mw request `catchError` errorHandler
      left =  (\x -> (++) "There was an error :" x)
      right = id
  in
    either left right response

The userInputLoop function is also updated to reflect the types change to the route function.

With these changes we are able to handle exceptions. If we type in "buggy" for the request string while running Main4.hs, we will notice that our request is handled by the errorHandler function.

By running main4, and providing buggy as input string, you notice that the errorHandler is invoked.

$ stack exec main4
Please type in the request
(one of 'handler1', 'handler2', 'handler3', 'buggy' or any string for
default handling)
buggy
There was an error returned: Error from routeHandlerBuggy

Fifth Iteration

One thing you will notice is that every routeHandler takes a String as an argument. This argument will represent the request information later on in the real Scotty library. A better way to capture this information would be to wrap it in a type and make the value available as input to a Reader monad. By wrapping in a new type we let the Scotty framework process the low level message and provide request arguments in different forms. In this section, we will continue to assume that the request parameter is still a String. But, we will make this value available through a Reader monad. Replacing the String with some kind of newtype will be straight forward later on.

The entire code for this section is available at Main5.hs.

The first thing we do in this iteartion is update the ActionT type.

type ActionT = Exc.ExceptT ActionError (Reader Request) Response

From the previous iteration, we replace Either to ExceptT. ExceptT is a monad transformer that will help wrap the Either type in a Reader monad. By, switching to ExceptT we are able to use the Reader that will accept the Request value.

Next, we update our client functions the routeHandlers to return the new ActionT type. Notice, that the signature of all the routerHandlers change and they no more accept a String as an argument. The input is retrieved with ask. Here, are the definitions of the new routerHandlers.

-- client functions
routeHandler1 :: ActionT
routeHandler1 = do
  input <- ask
  return $ "middlware_func1 got input = " ++ input

routeHandler2 :: ActionT
routeHandler2 = do
  input <- ask
  return $ "middlware_func2 got input = " ++ input

routeHandler3_buggy :: ActionT
routeHandler3_buggy = throwError "error from buggy handler"

routeHandler3 :: ActionT
routeHandler3 = do
  input <- ask
  return $ "routeHandler3 called = " ++ input

Notice that the only change we had to make to the routerHandler was to switch its signature and ask for the input using the Reader monad.

Next, we will look at the changes we need to make to the framework functions. The change we have to do is to the route and runAction functions. We have to unwrap the ExceptT monad stack which we will do in the runAction function.

route :: ActionT -> (String -> Bool) -> Route
route mw pat mw1 input_string =
  let tryNext = mw1 input_string in
  if pat input_string
  then
    let x = runAction mw input_string
        y = fromMaybe "" x
    in
      y
  else
    tryNext

runAction ::
  Exc.ExceptT ActionError (Reader Request) Response
  -> String -> Maybe String
runAction action request =
  let response = flip runReader request
                 $ Exc.runExceptT
                 $ action `catchError` errorHandler
      left =  (\x -> Just $ (++) "There was an error :" x)
      right = Just
  in
    either left right response

The runAction is called from route for the first matching route. Notice, that we perform the following steps:

We run the action using catchError so that any exception raised by the routerHandlers is processed by the errorHandler. To run the action we first unwrap it using runExceptT. This gives us the inner monad which is the Reader. Now we run the Reader monad, by passing it the request string. Finally, the response is returned as a Right value if the processing was successful or a Left value if an error was raised. The errorHandler captures both the input and the error message that was thrown by one of the route handlers.

errorHandler :: String -> ActionT
errorHandler error = do
  input <- ask
  return $ "There was an error returned for input=" ++ input ++ ", error=" ++ error

So, with that we are able to wrap our ActionT in a Reader as well as still retain our Either monad to capture errors as well.

Sixth Iteration

This will be our last iteration before we start looking at the real thing. One last thing we want to do is change the type of our Response. So far we have set the type of Response to be a String. But, while building a framework, we want to be able to create layers of middleware where the response can get updated by any of these layers. That also allows adding headers and other information to the response before it is sent to the outside world. Therefore, that will be the goal of this iteration.

The full source for this iteration can be found at Main6.hs.

As in the previous iteration, we first update our ActionT type.

type ActionT a = Exc.ExceptT ActionError (ReaderT String (ST.State Response)) a

In contrast to our type in previous interaction, we wrap the Response in a State monad. And, since we also want to retain our Reader monad, we update the Reader monad to ReaderT monad which helps us stack the Reader and State monads. Everyone visualizes these stacking in different ways, so there is no attempt made here to describe it! The type of ActionT you see here is almost close to what Scotty uses. So, it is helpful to review it and understand how the monads are stacked up.

We now need to fix the runAction from the previous iteration, to take care of the change to ActionT. All we need to do here is add runState to the unwrapping statements, since that is the only new layer we added. Everything else in runAction remains the same.

runAction :: ActionT () -> Request -> Maybe Response
runAction action request =
  let (a, s) = flip ST.runState ""
               $ flip runReaderT request
               $ Exc.runExceptT
               $ action `catchError` errorHandler
      left = const $ Just "There was an error"
      right = const $ Just s in
    either left right a

The changes we need to make to the routerHandlers are a bit involved. Note, that we ask for the input string the same way we did in our previous iterations. But, now we need to return a State monad that accepts a response value as state. Since, the State monad is tucked away three levels deep in a Reader and then in a Either monad, we need to apply lift twice. (Note, that in the actual scotty implementation, the ActionT is a new type and it is an instance of various Monad classes. Which allows us to skip the explicit applying of lift operation while using Scotty as the library). Here is the list of the routeHandlers that go with this iteration.

routeHandler1 :: ActionT ()
routeHandler1 = do
  input_string <- ask
  let st =
        ST.modify
        (\_ -> constructResponse ["request:" ++ input_string, "processed by routeHandler1"])
  lift . lift $ st

routeHandler2 :: ActionT ()
routeHandler2 = do
  input_string <- ask
  lift . lift $ ST.modify  (\s -> s ++ input_string ++ " inside middleware func 2")

routeHandler3_buggy :: ActionT ()
routeHandler3_buggy = throwError "error from buggy handler"

routeHandler3 :: ActionT ()
routeHandler3 = do
  input_string <- ask
  lift . lift $ ST.modify (\s -> s ++ input_string ++ " inside middleware func 3")

With these changes, we have almost built the skeleton of the framework that represents the data structures and implementation of Scotty. With this understanding, we are ready to go ahead and start studying how the different parts of Scotty work together.

This chapter allowed us to build through a toy framework from very basic types to some advanced uses of monads. Hopefully, you were able to walk through this chapter and understand how we went about updating our coding across different iterations. With this knowledge at hand, it should be easier to look at the Scotty implementation in the following chapter. Given that we were able to reason through the different iterations, the same reasoning can be applied while we read through the implementation.

Sample Web Application

We start with a simple web application built using Scotty. The application will have two end-points. One end point will return a message formatted in HTML. The second end point accepts a parameter in the form of a query-string and embeds it into a dynamically generated HTML string and returns the result.

main :: IO ()
main = scotty 3000 $ do
  get "/" $ do
      html $ "Read you a Scotty!"
  get "/:username" $ do
    username <- param "username"
    html $ mconcat [
         "<h1>Hello, ", username,  "</h1>", "Hope you enjoy reading this book"]

We will refer back to this example as we read through the Scotty implementation. We will also update our example with more features as we try to reason with some of the approaches taken in the implementation of Scotty.

Let us look closely at this example. In the main function we call scotty with two arguments. The first argument is the port number on which we want the web application to listen on. The second argument to scotty is a value of type ScottyT Text IO. We will look at this type in detail later. But, for now it is enough to understand that this wraps a state monad whose state contains the configuration of the web application. The configuration would be the different HTTP methods(GET, POST, etc.), the route patterns (/index, /, etc.) the web application supports. Henceforth, we will refer to this argument as ScottyT or more generally as scotty state.

The scotty state is built using functions like get
[other functions would be post, put, delete etc. Refer to (Scotty.hs)]
. The first argument to get is a string which specifies the url pattern. The second argument is the more interesting one. The argument is of type ActionT e m a. The ActionT e m a is a monad that stacks a few monads under it. Henceforth, we will refer to this argument as the action. We will continue to use this term to refer to this argument through this book. More specifically, throughout this book, we will assume the application is instantiated with default configuration. Therefore the e in Action T would be a value of ActionError and m would be the IO monad. The a would vary depending on the effect of the monad.

At the high level, here is what is happening. Each call to get accepts an url pattern and an action that needs to be performed if a client request matches the url pattern. Each call to get adds a route to the scotty state. Therefore, a route contains the action that has to be performed for a request made to a specific url pattern. The scotty state contains the list of routes that it can run every request through until one of the routes successfully processes the request. In the sample application above we add two routes to the scotty state. The first route contains the action,

do
      html $ "Read you a Scotty!"

and the second route contains the action

$ do
    username <- param "username"
    html $ mconcat [
         "<h1>Hello, ", username,  "</h1>", "Hope you enjoy reading this book"]

When the request arrives, either the route successfully executes (on a match) by running the request through the action and returning a responses or passes the request on to the next route on the list. For example, if our request url looked "http://readyouascotty.com/", then "/" matches our request then the action which returns "Read you a Scotty!" will be run. Or the next route is checked and so on.

The concept is consistent with any web application one might have created using other languages/frameworks. Our objective is to wrap our head around how this whole process is handled in the implementation. We want to understand what the scotty state entails. We want to understand why we need ActionT. We will see how the requests are threaded across different routes, parameters parsed and errors handled. I hope this helps us identify patterns that we could use in our own projects.

Entry Points and Settings

The scotty app can be configured in a number of ways. All options can be reviewed at Scotty.hs.

Some options available are as follows

  • scotty - This is the simplest. This function takes a port and the route handlers we will be looking at shortly

  • scottyOpts - This function provides more options to run the scotty app. The warp server is the backend for Scotty.

  • scottySocket - To run the Scotty app by listening to the warp server on an Unix socket.

  • scottyApp - This is more to turn the application into another middleware of an WAI application which can be used by any handler. The WAI library can be viewed as the middleware siting between Scotty and the warp server.

These functions are wrappers around the functions in Trans.hs. We will look at these functions in detail in later chapters.

Next, we will look at the data type that can be used to configure the server. As stated earlier, the scottyOpts function take a value of Options record data type. The Options data type is declared in Types.hs

Options
data Options = Options { verbose :: Int
                       , settings :: Settings }

The settings attribute holds the warp server settings. The app settings is an abstract data type that can be accessed through the provided default constructor and a group of setter methods as defined under warp settings

Declaring routes

From the sample web application, we see that the third parameter to the scotty function is a list of actions that needs to be performed if the request matches the route pattern specified as the second argument. Every time a request needs to be processed, we want to be able to match the request to the url pattern and use the respective action to process the request. Therefore, we want want to wrap each action in a route. Hence we create a set of routes to handle request to different url patterns. We will store this information in the scotty state.

We want any client of Scotty to be able to create a route handler for each route pattern. One way we can do that is to thread the request through a list of routes handlers until one of the routes wraps an action that succeeds. Every route handler should take a Request type and return some m Response type (eg. IO Response). We also want to thread our requests to the next route handler. Therefore, we a need to create a route value whose type would be to process a request using a particular action and also accept another route handler that can be used if the request cannot be processed with the given action.

Therefore, we would end up with a type that looks conceptually as follows. Notice, that return value is still of type Response.

Request -> (Request -> Response) -> Response

This is exactly the kind of type we built upon in the toy Scotty framework we built.

Let us now walk through some of the real types that help us build these states.

----- Transformer Aware Applications/Middleware -----
type Middleware m = Application m -> Application m
type Application m = Request -> m Response

These two types hide the Application and Middleware types from Network.Wai. Network.Wai is the backend interface to a library like warp. The Application type is self-explanatory. It is a function takes a Request and returns a Response wrapped in some monad m. The default Application type provided by Network.Wai has this type,

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

The reason why Scotty abstracts over this type will become clearer later on. For now, it is sufficient to understand that with the local Application type Scotty can wrap the Response in a stack of monads that will abstract away some of the error handling that would be required. Notice, this Application type differs from our toy example. This is due some redirection introduced by Network.Wai library to control the ResponseReceived values returned by each Application.

Scotty also declares a Middleware type. This type is an example of continuation-passing style where a value of type Middleware takes an Application and then decides to delegate the call to its second parameter which happens to be another Application. Using, this pattern we can thread a request through different Application values until the request in successfully processed. This type also gives Scotty the ability to thread a request through a pipeline of Middleware values. The route value we were looking for in the earlier will be a example of Middleware value. With the initial setup of our sample application, we end up with a list of routes which are of type [Middleware m]. Note, that this type aligns with the type the route function in the toy example was using.

Let us now see how the above two types are used.


--------------- Scotty Applications -----------------
data ScottyState e m =
    ScottyState { middlewares :: [Wai.Middleware]
                , routes :: [Middleware m]
                , handler :: ErrorHandler e m
                }

In this chapter we will focus on the routes attribute. The routes attribute is a list of routes that Scotty needs to thread every request through till the request is successfully processed. As we discussed earlier, another way to look at the type of one element of routes would be

route:: Middleware m

route:: Application m -> Application m

route ::  (Request -> m Response) -> (Request -> m Response)

route ::  (Request -> m Response) -> Request -> m Response

So, we see that an element of routes is a type that take a function that turns a Request into m Response. In the process, it also receives another function as a continuation that can be used if the first function argument cannot process the request successfully. The tricky thing to observe for a some of us would be to see that the final return value of this function in still m Response, even though the above organization makes it look like a Middleware value is returned. We specifically state the return value of this function is m Response, since that is what is required to interact with the Network.Wai layer.

How does Scotty configure these routes? Lets take a look at a Hello, Scotty app. The third parameter to the scotty function is a monad. More specifically, it is a State monad of type

newtype ScottyT e m a = ScottyT { runS :: State (ScottyState e m) a }
    deriving ( Functor, Applicative, Monad )

Scotty uses this state monad to register the list of actions, where each action is wrapped in one route. For example every action listed in the third argument to scotty function returns a ScottyT e m a and the state monad captures all the actions in its state.

Let us take a look at how this is done.

  get "/:word" $ do
          beam <- param "word"
                  html $ mconcat ["<h1>Scotty, ", beam, " me up!</h1>"]

The get function resolves to addroute GET function in


-- | get = 'addroute' 'GET'
get :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
get = addroute GET

-- | Define a route with a 'StdMethod', 'T.Text' value representing the path spec,
-- and a body ('Action') which modifies the response.
--
-- > addroute GET "/" $ text "beam me up!"
--
-- The path spec can include values starting with a colon, which are interpreted
-- as /captures/. These are named wildcards that can be looked up with 'param'.
--
-- > addroute GET "/foo/:bar" $ do
-- >     v <- param "bar"
-- >     text v
--
-- >>> curl http://localhost:3000/foo/something
-- something
addroute :: (ScottyError e, MonadIO m) => StdMethod -> RoutePattern -> ActionT e m () -> ScottyT e m ()
addroute method pat action = ScottyT $ MS.modify $ \s -> addRoute (route (handler s) (Just method) pat action) s

The core function to understand is the addRoute function. The function takes a StdMethod which specifies one of the Http request methods. The second parameter is the route pattern. For example "/index" or "/:name" etc. The third parameter is the action that is going to be performed for the given request. Notice that each each action is wrapped inside a route closure. This is the parameter that is provided as the second parameter to get as an action value.

Lets look closely at the addroute function. It returns ScottyT object which is the state monad that wraps the ScottyState. The computation is the state monad is just weaving the state through modify. modify accepts a function whose first argument accepts a state and returns a modified state. So, what is this function doing?

The function provided to modify, adds a route to the ScottyState.routes attributes. Recollect, that the each route is of type Middleware m. That is, it takes a (Request → m Response) and a fallback (Request → m Response). The route function creates the request Middleware m that gets added as a route to ScottyState.

We will look at the route function in detail later on. But for now it is enough to understand that the route function wraps the action that needs to be performed for the request. For the novice haskeller, this a great example of power of currying. We seamlessly, create a route value, by providing just the first 4 parameters. The only remaining parameter to this function is Middleware m. When this function gets called later, the Application (which happens to be the next route in the list of routes and the Request object are provided. Therefore, the types check out. Take a minute and reason how the addRoute function returns a value of type Middleware m when called inside the State monad. Then think about how a Request and Application m can be passed to this function at a later time.

route :: (ScottyError e, MonadIO m) => ErrorHandler e m -> Maybe StdMethod -> RoutePattern -> ActionT e m () -> Middleware m
route h method pat action app req =
    let tryNext = app req
        {- |
          We match all methods in the case where 'method' is 'Nothing'.
          See https://github.com/scotty-web/scotty/issues/196
        -}
        methodMatches :: Bool
        methodMatches =
            case method of
                Nothing -> True
                Just m -> Right m == parseMethod (requestMethod req)
    in if methodMatches
       then case matchRoute pat req of
            Just captures -> do
                env <- mkEnv req captures
                res <- runAction h env action
                maybe tryNext return res
            Nothing -> tryNext
       else tryNext

Now, looking closely, when the route gets added to the list of routes, the parameters provided to this function are ErrorHandler e m, Maybe StdMethod, RouterPattern, ActionT e m. The remaining parameters are provided when the client requests arrive. When the client requests arrive, first the ActionT e m () value is run using runAction and if that action fails, then tryNext is called which passes the Request on to the next Application. The next handler could be any Middleware m (that is another route or an arbitrary middlware).

One way to understood the type of this function, is to flatten it out as follows

Resolving the types of route

route :: (ScottyError e, MonadIO m) => ErrorHandler e m -> Maybe
StdMethod -> RoutePattern -> ActionT e m () -> Middleware m

route :: (ScottyError e, MonadIO m) => ErrorHandler e m -> Maybe
StdMethod -> RoutePattern -> ActionT e m () -> (Application m ->
Application m).

route :: (ScottyError e, MonadIO m) => ErrorHandler e m -> Maybe
StdMethod -> RoutePattern -> ActionT e m () -> (Request ->  m Response) ->
(Request -> m Response)

Therefore, using the flattened type signature, we see that

  1. When route is added to the routes attribute, we add a curried function of type (Request -> m Response -> Request -> m Response).

  2. When the request actually has to be processed, the curried function is then invoked with the next route in the list that happens to be of type Middleware. But, when all middlewares are applied, the final type resolves to type Request -> m Response.

  3. Now the function is applied to a Request value. The runAction on the request either succeeds or on failure, the Request is passed on to next Application m.

In this section, we explored how the third parameter we passed to scotty function is used to configure a list of routes, which each route captures the url pattern of the requests it can service and the action that needs to be applied to the requests when the url pattern matches. This also aligns with toy scotty we built using a similar route function.

Initializing the App

In the previous chapter, we looked at how the routes get built when the entry point of our app is called.

So far, all the statements under do [expression] which was the third parameter to the scotty function has been evaluated and all routes added to the state of the ScottyT e m a. For our purpose, this type resolved to ScottyT e IO (). The e is for error-handling and we will take a look at it later.

If you are interested in the call trace so far, here it is

Scotty.scotty → Trans.scottyT → Trans.scottyOpsT.

Now, let us take a look at scottyOpsT where our web application starts listening and serving requests.

-- | Run a scotty application using the warp server, passing extra options.
-- NB: scottyOpts opts === scottyOptsT op
scotidtyOptsT :: (Monad m, MonadIO n)
            => Options
            -> (m Response -> IO Response) -- ^ Run monad 'm' into 'IO', called at each action.
            -> ScottyT e m ()
            -> n ()
scottyOptsT opts runActionToIO s = do
      when (verbose opts > 0) $
              liftIO $ putStrLn $ "Setting phasers to stun... (port " ++ show (getPort (settings opts)) ++ ") (ctrl-c to quit)"
    liftIO . runSettings (settings opts) =<< scottyAppT runActionToIO s

The runSettings function is from Network.Wai.Handler.Warp. Its type is

runSettings :: Settings -> Application -> IO ()

The (settings opts) returns the Settings value. We looked at the the Options record type in Types.hs earlier.

runSettings is first called with settings. The second parameter to runSettings is

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

We build this value using scottyAppT runActionIO s. The runActionIO is set to id and s is the value of ScottyT e m () which is the state of the web application. Now, we turn our attention to scottyAppT tht will produce the `Application value needed.

-- | Turn a scotty application into a WAI 'Application', which can be
-- run with any WAI handler.
-- NB: scottyApp === scottyAppT id
scottyAppT :: (Monad m, Monad n)
           => (m Response -> IO Response) -- ^ Run monad 'm' into 'IO', called at each action.
           -> ScottyT e m ()
           -> n Application
scottyAppT runActionToIO defs = do
    let s = execState (runS defs) def
    let rapp req callback = runActionToIO (foldl (flip ($)) notFoundApp (routes s) req) >>= callback
    return $ foldl (flip ($)) rapp (middlewares s)

As a first step, we execState of ScottyT e m(). This creates all the routes that were declared in our app. Recollect, the execState invokes the state monad ScottyT e m() that was returned by consecutive calls to addroute as each of our do <expressions> were evaluated. This statement evaluates the route function we looked at in the previous chapter.

let s = execState (runS defs) def

Now we need to return a function that ultimately takes a Request and returns a m Response. In other words it is the Application m type we have in Types.hs.

There are a couple of things we need to have. We want to thread a Request through all the routes. Once one of the `routes returns a IO Response, we will have to apply all middlewares in the same order they appear in the list. Therefore, we do two things, we defined a function rapp which is of the following type

rapp:: Request -> (Response -> IO ResponseRecieved)
rapp req callback = ...

When we fold over all the user defined routes and middleware we want something like

M1 $ ( M2 $ ...Mn ($ ( rapp )

And then rapp expands to

M1 $ ( M2 $ ...Mn ($ ( R1 -> R2 -> ....-> notFoundApp))

where R1, R2, ..Rn are the list of routes of type Middleware m. And since rapp takes two other parameters, the returned type from scottyAppT is a function that takes the Request and returns Response m. And since we run this whole function in a IO Monad in our case, we get back

IO (Request -> IO Response)
-- which can also be written asciidoc
IO (Application)

-- and replacing with generic monad, we have
n Application

Now, going back to scottyOptsT, where we had a call to scottyAppT, we apply runSettings (settings opts) to the its return value IO Application.

Therefore, using scottyOptsT we were able to initialize the Network.Wai interface to start listening to user requests.

The core of the initialization happens in the scottyAppT or one of its variants in the Scotty library.

Handling requests

So far we have seen how we set up the state of a Scotty app and then also studied how the web app is started before it starts serving requests.

One important thing to recollect that we learned during this process was the Scotty state updates itself with the list of routes as defined in the declaration of the web app. Each of the routes that are defined is a function that contains the action that needs to be performed once the incoming Request for a route matches the pre-defined routes.

There are 2 important functions that handles this process. We already saw one function in the chapter on routes where we briefly talked about route function. This was the function that captured the action that was provided for each route. The second function we will discuss will be runAction.

Let’s take a look at each of these functions.

route :: (ScottyError e, MonadIO m) => ErrorHandler e m -> Maybe StdMethod -> RoutePattern -> ActionT e m () -> Middleware m
route h method pat action app req =
    let tryNext = app req
        methodMatches :: Bool
        methodMatches =
            case method of
                Nothing -> True
                Just m -> Right m == parseMethod (requestMethod req)
    in if methodMatches
       then case matchRoute pat req of
            Just captures -> do
                env <- mkEnv req captures
                res <- runAction h env action
                maybe tryNext return res
            Nothing -> tryNext
       else tryNext

The route function is called during the setting up of routes attribute of ScottyState data type. This function is called for each route that is declared in our web application. The function is initially called with an ErrorHandler e m (attribute of ScottyState), the StdMethod value (the request type GET, POST etc), the RoutePattern (the patterns like /index), and the action of type ActionT e m(). We will look that ActionT e m () when we discuss runAction. Once, these three arguments are applied, we have a function type Middleware m.

This is the function that will be called while processing each request as we look through each route to satisfy a request. In other words, the list of these functions form the list of routes or list of Middleware m.

The route function, when called checks if the request method and route pattern match what the given action can process. On a match, first the the Request value req is parsed using mkEnv into the ActionEnv type.

data ActionEnv = Env { getReq       :: Request
                     , getParams    :: [Param]
                     , getBody      :: IO ByteString
                     , getBodyChunk :: IO BS.ByteString
                     , getFiles     :: [File]
                     }

Recollect, that the function type of route function at this point is Middleware m. That is

Application m -> Application m
-- that expands out to
Application m -> Request -> m Response

Once, we have the request parsed, we run the request through the ActionT e m(). If running the ActionT e m succeeds, we return, or else we pass the request on to the next Application m. This continues until the request can be satisfied or until the notFound value is found. Note that the notFound value is the last Application value attached in the scottyAppT `. That allows the `types to check out and finally have a function that takes a Request and returns a m Response.

We will shortly turn our attention to 'runAction` function. Before, that we will look closely at ActionT e m ()

newtype ActionT e m a = ActionT { runAM :: ExceptT (ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a }
            deriving ( Functor, Applicative, MonadIO )

Let us unwrap this transformer stack. Refering back to the toy application may help at this point! The ScottyResponse type

data ScottyResponse = SR { srStatus  :: Status
                         , srHeaders :: ResponseHeaders
                         , srContent :: Content
                         }

This type packs the response that is delivered across the Middleware m values as the request is processed by each middleware. This is similar to the simpler Response type we had in out toy application.

The a usually will be () since each action updates the state which is the ScottyResponse. This is discussed in the next chapter.

The StateT object is run inside ReaderT and the Reader monad makes the ActionEnv value available to the action. In our web application, we use the param function to access the parameters that are submitted along with the request. The param function wraps the ask functions of the Reader monad. We will explore the code that parses the params seperately. ExceptT wraps the action and also a error value ActionError e if the processing of the response fails.

The use of this value is best understood by its use in the runAction function.

newtype ActionT e m a = ActionT { runAM :: ExceptT (ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a }
    deriving ( Functor, Applicative, MonadIO )
-- Nothing indicates route failed (due to Next) and pattern matching should continue.
-- Just indicates a successful response.
runAction :: (ScottyError e, Monad m) => ErrorHandler e m -> ActionEnv -> ActionT e m () -> m (Maybe Response)
runAction h env action = do
    (e,r) <- flip MS.runStateT def
           $ flip runReaderT env
           $ runExceptT
           $ runAM
           $ action `catchError` (defH h)
    return $ either (const Nothing) (const $ Just $ mkResponse r) e

The runAction is where all the unpacking is happening. The catchError function runs the ActionT e m a monad if that raises an error, then handles the error using the defH h handler. The defH h handler handles exception.

Now, lets look at how the action is run.

  1. runAM returns ExceptT

  2. runExceptT returns the ReaderT

  3. Since, runReaderT takes the reader and then the environment, we apply flip to runReaderT. This way we can apply the env and then provide the actual Reader monad as a parameter.

  4. Similarly, we unwrap the StateT , apply flip so that we can apply the function to def before we apply the function to wrapped state.

  5. This computation returns (e, r., where e is a Maybe type and r is the state that holds the response that is created so far.

  6. either return Maybe value of the Response.

What this means is, the Request parameters are available in env. Therefore, using the params function we can access those values. Also, in our sample app, the action returns a modified Response. That is the state in ScottyResponse is updated in each action. In summary, any function whose type as ActionT e m a, has access to Reader monad related functions to ask for request params and also also has access to State monad related functions like modify to update the Response.

This actual accessing of Request and update of Response will discussed in the later chapters. It could be useful to refer back to this section while reading about how parameters are handled and how the response is updated.

Acessing Request Parameters

Let us start with an example that uses the query parameters that is passed along with the request

get "/:username" $ do
    username <- param "username"
    --  use username in the action

As we have seen earlier, the third parameter to the get function is the ActionT e m a value. Therefore, param also returns a ActionT e m a values, where a will either be the value of username passed in the request if the parameter is found or it might return an error.

In this section we will study how the request parameters are parsed in Scotty. Recall, that in route function, we have a call to mkEnv. This function captures all the information about the request into the ActionEnv record.


data ActionEnv = Env { getReq       :: Request
                     , getParams    :: [Param]
                     , getBody      :: IO ByteString
                     , getBodyChunk :: IO BS.ByteString
                     , getFiles     :: [File]
                     }

The getParams attribute of this record type captures all the request params.

The two functions used to lookup parameters are defined as follows:

param :: (Parsable a, ScottyError e, Monad m) => T.Text -> ActionT e m a
param k = do
    val <- ActionT $ liftM (lookup k . getParams) ask
    case val of
        Nothing -> raise $ stringError $ "Param: " ++ T.unpack k ++ " not found!"
        Just v  -> either (const next) return $ parseParam v

-- | Get all parameters from capture, form and query (in that order).
params :: Monad m => ActionT e m [Param]
params = ActionT $ liftM getParams ask

Recollect, ActionT wraps the ReaderT monad. Therefore, the ActionEnv values is passed in as the environment. ask returns ActionEnv and then getParams returns [Params]. We liftM getParams since ask is Reader m a. We put the value back into ActionT before returning. All parameters are parsed using the ` parseParams` method of the Parseable type class.

Other functions defined in Action.hs that can be used to access Request are as follows:

-- | Get the 'Request' object.
request :: Monad m => ActionT e m Request
request = ActionT $ liftM getReq ask

-- | Get list of uploaded files.
files :: Monad m => ActionT e m [File]
files = ActionT $ liftM getFiles ask

-- | Get a request header. Header name is case-insensitive.
header :: (ScottyError e, Monad m) => T.Text -> ActionT e m (Maybe T.Text)
header k = do
    hs <- liftM requestHeaders request
    return $ fmap strictByteStringToLazyText $ lookup (CI.mk (lazyTextToStrictByteString k)) hs

-- | Get all the request headers. Header names are case-insensitive.
headers :: (ScottyError e, Monad m) => ActionT e m [(T.Text, T.Text)]
headers = do
    hs <- liftM requestHeaders request
    return [ ( strictByteStringToLazyText (CI.original k)
             , strictByteStringToLazyText v)
           | (k,v) <- hs ]

-- | Get the request body.
body :: (ScottyError e,  MonadIO m) => ActionT e m BL.ByteString
body = ActionT ask >>= (liftIO . getBody)

-- | Get an IO action that reads body chunks
--
-- * This is incompatible with 'body' since 'body' consumes all chunks.
bodyReader :: Monad m => ActionT e m (IO B.ByteString)
bodyReader = ActionT $ getBodyChunk `liftM` ask

-- | Parse the request body as a JSON object and return it. Raises an exception if parse is unsuccessful.
jsonData :: (A.FromJSON a, ScottyError e, MonadIO m) => ActionT e m a
jsonData = do
    b <- body
    either (\e -> raise $ stringError $ "jsonData - no parse: " ++ e ++ ". Data was:" ++ BL.unpack b) return $ A.eitherDecode b

All the above listed functions work on the ActionEnv value mentioned earlier. The mkEnv function is responsible for creating this value from the raw request data. We do not discuss the details of this function in this book. But, if you are interested in understanding the lower level details of how the Request object is parsed into the ActionEnv value, then this function is where you should start.

mkEnv :: forall m. MonadIO m => Request -> [Param] -> m ActionEnv

Response

Finally, we look at how the responses are created. If you have followed along than you have would have noticed that the ActionT values holds the Response in its state. The response is created during the call to runAction function. Here is the example we started with

get "/:username" $ do
    username <- param "username"
    html $ mconcat ["<h1> Hello, ", username , "</h1>"]

The action is run in the ActionT monad. The call to param leaves the state unchanged. The call to html, as seen below, along with the raw function updates the state in the ActionT.


-- | Set the body of the response to the given 'T.Text' value. Also sets \"Content-Type\"
-- header to \"text/html; charset=utf-8\" if it has not already been set.
html :: (ScottyError e, Monad m) => T.Text -> ActionT e m ()
html t = do
    changeHeader addIfNotPresent "Content-Type" "text/html; charset=utf-8"
    raw $ encodeUtf8 t

The html function adds a header to the response and applies raw to the encoded text.

-- | Set the body of the response to the given 'BL.ByteString' value. Doesn't set the
-- \"Content-Type\" header, so you probably want to do that on your
-- own with 'setHeader'.
raw :: Monad m => BL.ByteString -> ActionT e m ()
raw =
ActionT . MS.modify . setContent . ContentBuilder . fromLazyByteString

Here the raw function create a Content value and set the srContent attribute of the ScottyResponse value. Notice, that raw has a return type of ActionT e m (). This function updates the state in ActionT. The state in ActionT is the response that is accumulated before it is served.

Other functions that can be used to send different responses are as follows:

-- | Send a file as the response. Doesn't set the \"Content-Type\" header, so you probably
-- want to do that on your own with 'setHeader'.
file :: Monad m => FilePath -> ActionT e m ()
file = ActionT . MS.modify . setContent . ContentFile

-- | Set the body of the response to the JSON encoding of the given value. Also sets \"Content-Type\"
-- header to \"application/json; charset=utf-8\" if it has not already been set.
json :: (A.ToJSON a, ScottyError e, Monad m) => a -> ActionT e m ()
json v = do
    changeHeader addIfNotPresent "Content-Type" "application/json; charset=utf-8"
    raw $ A.encode v

-- | Set the body of the response to a Source. Doesn't set the
-- \"Content-Type\" header, so you probably want to do that on your
-- own with 'setHeader'.
stream :: Monad m => StreamingBody -> ActionT e m ()
stream = ActionT . MS.modify . setContent . ContentStream

Therefore, we have seen that having the functions discussed above run in the ActionT monad helps them modify the Response which is finally returned to the client. These functions, along with the functions we looked at in the previous chapter, all run in the ActionT monad and therefore can ask for parameters and modify the response.

Epilogue

The Scotty library is a light weight library to build web applications. It also provides a good introduction to practical implementation of Haskell based programs. The purpose of this book is to help the user navigate through the source code of the Scotty library.

We started with a toy framework to build up a mental model on the requirements of the framework and how we could build one. With this we developed the intuition to understand some of the core functionalities the Scotty library had to implement to run our sample web application. We looked at the how the route declarations are handled. Then, we looked at how the state of the application is initialized. Following that we looked at the various functions to access the request information. Eventually, we explored some of the functions that can be used to create the response that can be served to the client.

This book does not walk through all the functions implemented in the Scotty library. But, it attempts to walk through the core functions that constitute the sequence of calls that occur right from receiving a request to processing the request and create the response that is eventually served.

For more thorough investigation and understanding of the library, the readers are encouraged to download the Scotty implementation and explore other aspects of the implementation.

I hope this short but intense read helped the reader look at a real world example of Haskell. In addition, I hope this book helped the reader understand the Scotty implementation itself.