Skip to content

Instantly share code, notes, and snippets.

@ollimandoliini
Created August 17, 2023 11:02
Show Gist options
  • Save ollimandoliini/0f93cd281fc2f0473ad306c37f3889fe to your computer and use it in GitHub Desktop.
Save ollimandoliini/0f93cd281fc2f0473ad306c37f3889fe to your computer and use it in GitHub Desktop.
effectful ♥️ servant

effectful ♥️ servant

In the Haskell world effect systems are currently a big thing and one of the most popular libraries on that front is effectful. When it comes to libries for creating webservices, the most popular one at the time of writing this is probably servant.

The two libraries go very well together but it isn't exactly obvious how you can marry them up since there doesn't seem to exist any examples at the moment. That's why I decided to create one. I'll go through setting up a simple service line by line and at the end of post I'll post the whole example. So if you're just after some quick boilerplate you can scroll right to the end.

If you haven't already, create a new project using cabal init -i. Then let's add some dependencies to our cabal file. You can probably get away with loosening most of the constraints but with those the example is guaranteed to work on ghc-9.2.7.

base                          >=4.7 && <5,
aeson                         >= 2.1.2 && < 2.2,
mtl                           >= 2.2.2 && < 2.3,
effectful                     >= 2.2.2 && < 2.3,
servant-server                >= 0.20 && < 0.21,
warp                          >= 3.3.28 && < 3.4

Next let's open our Main.hs file, add some imports and enable DataKinds language extension. The extension is required by both effectful and servant to enable having typelevel lists.

{-# LANGUAGE DataKinds #-}

module Main (main) where

import Control.Monad.Except (ExceptT (ExceptT))
import Data.Aeson (ToJSON)
import Effectful (Eff, IOE, runEff, (:>))
import Effectful.Error.Static (Error, runErrorNoCallStack, throwError)
import GHC.Generics (Generic)
import Network.Wai.Handler.Warp (run)
import Servant (
    Application,
    Capture,
    Get,
    Handler (Handler),
    JSON,
    Proxy (Proxy),
    ServerError,
    err404,
    hoistServer,
    serve,
 )
import Servant qualified ((:>))

Not much to say about the imports except that both libraries define :> operator and that is why we're importing servants one qualified.

Next, lets define a type synonym for our effect stack which is the most minimal stack we can use with servant. You can of course add more effects to your stack when you need.

type MyApp = Eff '[Error ServerError, IOE]

Then let's define a datatype that our services returns as well as a type for our servant API. Our API simply returns User entities based on userId.

data User = User
    { id :: Int
    , name :: String
    }
    deriving (Generic)

instance ToJSON User

type API = "user" Servant.:> Capture "userId" Int Servant.:> Get '[JSON] User

Then let's write the actual implementation of our API. Here we give the used effect explicitly in the constraints instead of using our MyApp type to limit the effects that can be used in the function. Here the only effect we want to allow is throwing HTTP errors.

app :: Error ServerError :> es => Int -> Eff es User
app userId =
    if userId == 1
        then pure (User 1 "olli")
        else throwError err404

Now to trickiest part of the post. In order to run our application we have to turn it into Handler which is the default type of servant applications. Furthermore, servant provides serve function which turns the Handler into Application type which can run with warp.

First, to turn our MyApp type to servants Handler we are going to use hoistServer function. That takes in three parameters: a proxy value to pass on the type of our application, a natural transformation of type (forall x. m x -> n x) that is used to do the actual conversion, and our application function.

The natural transformation part is the most interesting one. It's essentially a function where we peel of the layers of our effect stack one by one and package the resulting value into Handler type.

naturalTransformation :: MyApp a -> Handler a
naturalTransformation =
    Handler . ExceptT . runEff . runErrorNoCallStack

proxy :: Proxy API
proxy = Proxy

server :: Application
server = serve proxy (hoistServer proxy naturalTransformation app)

With our value of server we are now ready to run our application with run value from warp library.

main :: IO ()
main = run 8080 server

And that's it! I hope this post has been helpful for people starting out with servant and effectful.

As promised, the full code:

{-# LANGUAGE DataKinds #-}

module Main (main) where

import Control.Monad.Except (ExceptT (ExceptT))
import Data.Aeson (ToJSON)
import Effectful (Eff, IOE, runEff, (:>))
import Effectful.Error.Static (Error, runErrorNoCallStack, throwError)
import GHC.Generics (Generic)
import Network.Wai.Handler.Warp (run)
import Servant (
    Application,
    Capture,
    Get,
    Handler (Handler),
    JSON,
    Proxy (Proxy),
    ServerError,
    err404,
    hoistServer,
    serve,
 )
import Servant qualified ((:>))


type MyApp = Eff '[Error ServerError, IOE]

data User = User
    { id :: Int
    , name :: String
    }
    deriving (Generic)

instance ToJSON User

type API = "user" Servant.:> Capture "userId" Int Servant.:> Get '[JSON] User

app :: Error ServerError :> es => Int -> Eff es User
app userId =
    if userId == 1
        then pure (User 1 "olli")
        else throwError err404

naturalTransformation :: MyApp a -> Handler a
naturalTransformation =
    Handler . ExceptT . runEff . runErrorNoCallStack

proxy :: Proxy API
proxy = Proxy

server :: Application
server = serve proxy (hoistServer proxy naturalTransformation app)

main :: IO ()
main = run 8080 server
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment