Scala/Kotlin developer learning Haskell - Part 1 - Rest endpoint with JSON

7 minute read

I’ve been doing scala and FP for a while now, and during that time I’ve tried a couple of times to pickup haskell as well. What I noticed was that I knew too little about monad transformers, typeclasses and a lot of other concepts which are much more in the forefront when doing Haskell, compared to Scala (or Kotlin with Arrow for that matter). That combined with the foreign syntax, caused me to abandon those attempts.

So a new year, and a new attempt. This time I’m going to try by just building applications, since that usually seems to work best for me when learning a new language. So in this series prepare to see a lot of stupidly solved haskell issues, so bear with me.

Simple REST webservice: skeleton

As a first step I’m going to creat a very simple webservice, with just a couple of routes, and implement it using Haskell. I’ve been looking for a simple REST framework, and landed on Scotty https://github.com/scotty-web/scotty. Scotty is a haskell microservices framework that should be really easy to use.

After some messing around with all the different build tools, I’ve got a simple web server:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Web.Scotty (scotty, ScottyM, ActionM, text, get, param)

paramRoute :: ScottyM ()
paramRoute = get "/something/:id" $ do
  id <- param "id"
  text $ "this is a text with id: " <> id

main = do
  putStrLn "Start simple server"
  scotty 3000 $ do
    paramRoute

Which even returns what I expected!

curl -v localhost:3000/something/123
* Connected to localhost (127.0.0.1) port 3000 (#0)
> GET /something/123 HTTP/1.1
> Host: localhost:3000
> User-Agent: curl/7.54.0
> Accept: */*
>
< HTTP/1.1 200 OK
< Transfer-Encoding: chunked
< Date: Mon, 18 Feb 2019 18:07:37 GMT
< Server: Warp/3.2.26
< Content-Type: text/plain; charset=utf-8
<
this is a text with id: 123%

While the code is only a couple of lines. For me it took some effort to understand what is actually happening here. Let’s start at the top. {-# LANGUAGE OverloadedStrings #-} allows scotty to parse strings to a RouterPattern (more and that further down). Next we have some module definitions, and some imports which aren’t that interesting. Next lets look at the server entrpoint:

main = do
  putStrLn "Start simple server"
  scotty 3000 $ do
    paramRoute

Here we have a main method, which can output some IO stuff. It’s signature is main :: IO(). So the result of the main function should be an IO monad. I’ll get back to this monad in a later article, since it’s kind of special one. For now it is enough to know that the IO monad is used to do non-pure stuff like filo IO, stdout/stdin stuff, and I assume also network IO. With do we start a monad comprehension (just like the for-comprehensions from scala or binding approach from Arrow-KT). putStrLn returns an IO (), and scotty, which we use to launch the service, also results in an IO monad, so we can nicely combine these using do.

The signature of scotty is:

scotty :: Port -> ScottyM () -> IO ()

So we’ve already provided scotty with a port, and next we need to add a ScottyM () which will result in an IO(). Note that we can use a $ to separate function parts. In this case it means we first run the do paramRoute part, and pass the result into the scotty function (we could also have used parenthesis if we wanted).

You can see that we pass in the paramRoute which returns this ScottyM () function we need:

paramRoute :: ScottyM ()
paramRoute = get "/something/:id" $ do
  id <- param "id"
  text $ "this is a text with id: " <> id

This works because the signature of get is:

get :: RoutePattern -> ActionM () -> ScottyM ()

We pass in:

  • RoutePattern: This is the "/something/:id" string, which works because of the overloaded language feature.
  • do ...: And we pass in a monad comprehension, which should result in a ActionM () for us to return.

Scotty comes with a whole set of building blocks we can use to create the ActionM ()monad.

text :: Text -> ActionM ()
file :: FilePath -> ActionM ()
html :: Text -> ActionM ()
json :: ToJSON a => a -> ActionM ()

And provides other REST/HTTP related ActionM functions like:

param :: Trans.Parsable a => Text -> ActionM a
body :: ActionM ByteString
headers :: ActionM [(Text, Text)]

In our case we use the param function to get the id from the url, and the text function to create a ActionM (). And with that our function is done,
and our minimal webserver works.

Add more routes

With this basic setup we can easily add more routes by just creating functions that return a ScottyM:

paramRoute :: ScottyM ()
paramRoute = get "/something/:id" $ do
  id <- param "id"
  text $ "this is a text with id: " <> id

htmlRoute :: ScottyM ()
htmlRoute = get "/thisishtml" $ do
  html "<h1>Woohoo</h1>"

simpleRoute :: ScottyM ()
simpleRoute = get "/and/a/nested/one" $ do
  text "This is from the nested route"

-- entrypoint to the server
main = do
  putStrLn "Start simple server"
  scotty 3000 $ do
    paramRoute
    htmlRoute
    simpleRoute

Which is pretty convient, and actually pretty much similar as WebFlux does it or Akka-HTTP. At this point I was already pretty proud of myself, since I’ve come further with Haskell than in all my previous tries. When looking through the scotty doc I saw an example of how to add JSON support, so as a final step, let’s do that here as well.

Add JSON support

Scotty has standard JSON support using Aeson. And to use it, we can use the json function:

json :: ToJSON a => a -> ActionM ()

I had some trouble reading this function the first time I saw it. But apparently the stuff before the => tells us that we need to have a ToJson typeclass for the type a. So to use this, we need to define such an instance for our type. Looking at the documentation for ToJSON:

-- * The compiler can provide a default generic implementation for
-- 'toJSON'.
--
-- To use the second, simply add a @deriving 'Generic'@ clause to your
-- datatype and declare a 'ToJSON' instance...

So we can create a data type and add Generic to it (we also add Show to it, so we can print it from the REPL)

data Item = Item { itemId :: Int, name :: String, description :: String } deriving (Show, Generic)
instance ToJSON Item

And that should be enough. We can test this in the REPL using the encode function from Aeson (encode :: (ToJSON a) => a -> L.ByteString)

*Main Lib> import Data.Aeson
*Main Lib Data.Aeson> spork = Item {itemId = 1, name = "Spork", description = "Is it a spoon, is it a fork? I don't know!!"}
*Main Lib Data.Aeson> encode spork
"{\"itemId\":1,\"name\":\"Spork\",\"description\":\"Is it a spoon, is it a fork? I don't know!!\"}"

And it actually works. So we’ve created the ToJSON typeclass for our data type, and it seems to be automatically in scope as well, which is nice. So with this setup, we can add a new function that outputs JSON, and our complete example looks like this:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}

module Main where

import Web.Scotty (scotty, ScottyM, ActionM, text, html, get, param, json)
import GHC.Generics
import Data.Aeson (FromJSON, ToJSON)

data Item = Item { itemId :: Int, name :: String, description :: String } deriving (Show, Generic)
spork = Item {itemId = 1, name = "Spork", description = "Is it a spoon, is it a fork? I don't know!!"}

instance ToJSON Item

paramRoute :: ScottyM ()
paramRoute = get "/something/:id" $ do
  id <- param "id"
  text $ "this is a text with id: " <> id

htmlRoute :: ScottyM ()
htmlRoute = get "/thisishtml" $ do
  html "<h1>Woohoo</h1>"

simpleRoute :: ScottyM ()
simpleRoute = get "/and/a/nested/one" $ do
  text "This is from the nested route"

jsonRoute :: ScottyM ()
jsonRoute = get "/json" $ do
  json spork

-- entrypoint to the server
main = do
  putStrLn "Start simple server"
  scotty 3000 $ do
    paramRoute
    htmlRoute
    simpleRoute
    jsonRoute

And it works right away!

curl -v localhost:3000/json
* Connected to localhost (127.0.0.1) port 3000 (#0)
> GET /json HTTP/1.1
> Host: localhost:3000
> User-Agent: curl/7.54.0
> Accept: */*
>
< HTTP/1.1 200 OK
< Transfer-Encoding: chunked
< Date: Mon, 18 Feb 2019 19:18:46 GMT
< Server: Warp/3.2.26
< Content-Type: application/json; charset=utf-8
<
* Connection #0 to host localhost left intact
{"itemId":1,"name":"Spork","description":"Is it a spoon, is it a fork? I don't know!!"}%

Conclusions

Everything went suprisingly well this time. I didn’t run into too weird operators and syntax stuff and could focus on trying to understand what was happening in the code. I really enjoyed this first exploration of Haskell and was really pleasantly suprised.

Updated: