Write your own Discord bot in Haskell with Calamity

April 29, 2021

calamity is the most fully-featured library for writing Discord bots on Hackage, rivaling frameworks like discord.py and discord.js in features, while offering all the benefits of Haskell: a strong type system, pure functions, and risk-free refactoring. It may however seem impenetrable at first glance, using many language extensions such as TypeApplications, TypeFamilies, and DataKinds. It also uses the polysemy effect system rather than the more common mtl. The end result, however, is a very nice interface for making bots.

This post is intended to guide those less familiar with this part of the Haskell ecosystem on how to write their own bots using calamity and hopefully come out of the experience with a greater understanding of how to use these features and how they can be leveraged in their own programs and libraries. It’s possible to use calamity without understanding all the types involved, but it becomes significantly harder to debug and to understand any error messages you may get.

I recommend following along with the Hackage documentation open. You can search the haddocks by pressing s to open a search dialogue.

Libraries

polysemy

When writing real-world IO-heavy applications, it’s almost always advantageous to use an effect system for storing configuration data, error handling, incorporating state, etc. A common choice is mtl, the monad transformer library. polysemy is another such effect system that opts for working in a single monad, the Sem r monad, which is parameterized by a type-level list of effects, called the “effect row”.

Here’s an example snippet of code using mtl:

data Config = Config
  { cmdPrefix :: Text
  , ...
  }
handleMessage 
  :: (MonadReader Config m, MonadIO m)
  => String
  -> m ()
handleMessage msg = do
  prefix <- asks cmdPrefix
  when (prefix `isPrefixOf` msg) $
    liftIO $ putStrLn "Received a command: " <> msg

Using polysemy we’d instead work in the Sem r monad and require that the effect row contain the effects we need using Member, which takes an effect and an effect row and yields a constraint that the effect must be present in the effect row.

handleMessage 
  :: (Member (Reader Config) r, Member (Embed IO) r)
  => String
  -> Sem r ()
handleMessage msg = do
  prefix <- asks @Config cmdPrefix
  when (prefix `isPrefixOf` msg) $
    embed . putStrLn $ "Received a command: " <> msg

As you can see, all we have to do is declare which effects we require to be present in the effect row. polysemy also encourages using more granular effects instead of using IO, so we could have used the Trace effect instead and called trace function, which means all we require is that our effect row can log strings, whatever that may mean. This removes our dependency on the IO monad and makes our code more flexible.

handleMessage 
  :: (Member (Reader Config) r, Member Trace r)
  => String
  -> Sem r ()
handleMessage msg = do
  prefix <- asks @Config cmdPrefix
  when (prefix `isPrefixOf` msg) $
    trace $ "Received a command: " <> msg

How these effects are interpreted, and which concrete effect row is inferred depends on which effect interpreters we choose. For the Reader effect there’s really only one interpreter that polysemy provides to us, runReader :: i -> Sem (Reader i ': r) a -> Sem r a. The type signature says that given some value i we can handle a Reader i effect from the effect row. Remember that the effect row is just a type-level list of effects, so (Reader i ': r) just pattern matches on that list, a list with Reader i as its head and r as its tail. So the interpreter essentially strips an effect off the head of the effect row.

For interpreting the Trace effect we have a few options. We could gather all the logged messages into a list with runTraceList :: Sem (Trace ': r) a -> Sem r ([String], a), we could also just ignore the messages with ignoreTrace :: Sem (Trace ': r) a -> Sem r a. But in this case we’ll have the messages printed to stdout with traceToIO :: Member (Embed IO) r => Sem (Trace ': r) a -> Sem r a. Note that this interpreter requires that Embed IO be present in our effect list, meaning that our monad must be able to handle arbitrary IO actions. That’s fine, but now we’ll have to handle that effect as well. Since our goal is to eventually peel this onion into the IO monad, we’ll want some function that can convert some Sem r a into an IO a. That function would be runFinal :: Monad m => Sem '[Final m] a -> m a which takes a Sem with a singleton effect row containing just Final m for some monad m and returns a plain m a. To get such a Final m we can just use the embedToFinal :: (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a interpreter, which peels off an Embed m effect and delegates its effects to the Final m effect in our effect row.

Putting it all together:

main :: IO ()
main = runFinal
  . embedToFinal @IO
  . traceToIO
  . runReader (Config "!" ...)
  $ handleMessage "!polysemy"

This may seem a bit complicated, but it’s a method that lets us easily deal with all the effects we need, one at a time. The result is very clean. Note that we never deal with an explicit effect row, the type checker infers it for us based on the interpreters we choose.

di and di-polysemy

di is a fully-featured structured logging library. di-polysemy provides polysemy style effects for di. This is what calamity uses for logging.

lens

For a full understanding of how lens works, there are better resources such as the excellent lens over tea. This will just be a quick overview of the basic usage of lenses for those who aren’t familiar with them.

A lens can be thought of as a value that focuses on some part of a larger structure, such as a field in a record. For example, lens provides the _1 lens which focuses on the first element of a tuple. We can use a lens to extract part of a value with the view function or its operator counterpart, (^.):

ghci> view ('a', 5) _1
'a'
ghci> ('a', 5) ^. _2
5

We can replace part of a structure with the set function or its operator counterpart, (.~). We can use the flipped application operator (&) = flip ($) alongside this operator.

ghci> set _1 "hello" ('a', 5)
("hello", 5)
ghci> ('a', 5) & _2 .~ False
('a', False)

And finally, we have over and its operator %~ which work much the same way as set, but takes a function to modify the structure with rather than a set value.

ghci> over _1 succ ('a', 5)
('b', 5)
ghci> ('a', 5) & _2 %~ show
('a', "5")

Notably, we can compose lenses with the (.) operator from the Prelude to focus on parts of nested structures.

ghci> (True, ('a', 5)) ^. _2 . _1
'a'

generic-lens

The goal of using lens here is to be able to access the fields of the various record types that calamity exposes to us. We could use record accessors and update notation, but many of these records contain fields with the same name, so using them directly will lead to ambiguity errors. generic-lens solves this issue for us by allowing us to create lenses on the fly using the OverloadedLabels extension. For example, the Member type has a field called guildID. If we want to access this field from some member mem, we can simply write mem ^. #guildID.

Note that to use the field names as lenses the type must have an instance of the Generic typeclass. This can be done with the DeriveGeneric extension, which, unsurprisingly, allows the user to write deriving Generic. All, or at least most, of the record types defined in calamity have a Generic instance.

Creating the Skeleton

Let’s begin by building the skeleton for our project. Initialize a fresh cabal project by running cabal init in an empty directory. We’ll start by putting the adding the following dependencies in our bot.cabal file under build-depends.

  -- Use a version of `base` corresponding with GHC 8.10.x
  build-depends:
    , base             ^>=4.14
    , calamity         >=0.2.0 && <0.2.1
    , data-default
    , data-flags
    , di
    , di-polysemy
    , generic-lens
    , lens
    , polysemy
    , polysemy-plugin
    , text
    , text-show

polysemy-plugin is a GHC plugin for polysemy which improves type inference inside the Sem r monad. We have to enable it by adding -fplugin=Polysemy.Plugin to our GHC options.

  ghc-options:      -fplugin=Polysemy.Plugin

Let’s also start with a couple of language extensions.TypeApplications which lets us instantiate polymorphic values with concrete types, OverloadedStrings to be able to write Text literals, and OverloadedLabels for use with generic-lens. We’ll also need DataKinds later.

  default-extensions:
    DataKinds
    OverloadedLabels
    OverloadedStrings
    TypeApplications

We’ll build all these dependencies with cabal build --only-dependencies.

Let’s write the skeleton for the main function.

module Main where

import           Calamity
import           Calamity.Cache.InMemory
import           Calamity.Commands
import           Calamity.Commands.Context (useFullContext)
import           Calamity.Metrics.Noop
import           Control.Lens
import           Control.Monad
import           Data.Default
import           Data.Generics.Labels      ()
import           Data.Maybe
import           Data.Text                 (Text)
import qualified Data.Text                 as T
import qualified Di
import           DiPolysemy
import qualified Polysemy                  as P

main :: IO ()
main = Di.new $ \di ->
  void
  . P.runFinal
  . P.embedToFinal @IO
  . runDiToIO di
  . runCacheInMemory
  . runMetricsNoop
  . useFullContext
  . useConstantPrefix "!"
  . runBotIO (BotToken "<token>") defaultIntents
  $ do
    info @Text "Setting up commands and handlers..."

Let’s break this down bit by bit.

Di.new has the type

new :: (Di Level Path Message -> IO a) -> IO a

It’s a bit more polymorphic than that, but we’re just using it in plain IO. It essentially provides us a Di Level Path Message using a continuation. That value can be thought of as a sort of handle to the logger.

Now for the effect interpreters.

-- snip --
  . runBotIO (BotToken "<token>") defaultIntents
-- snip --

-- `runBotIO` has the type:
runBotIO
  :: forall r a. ( Members '[Embed IO, Final IO, CacheEff, MetricEff, LogEff] r
                 , Typeable (SetupEff r))
  => Token
  -> Intents
  -> Sem (SetupEff r) a
  -> Sem r (Maybe StartupError)

runBotIO is the main effect interpreter. It may look daunting, but let’s break it down piece by piece. Firstly, we’ll note it takes a Token and an Intents as inputs. A Token, as you can see in our skeleton, can be constructed using the BotToken constructor. An Intents is just a Word32 representing a bunch of binary flags. You can combine these intents and manipulate them with methods from the Flags typeclass from the data-flags package.

SetupEff r is a type alias for Reader Client ': (AtomicState EventHandlers ': (Async ': r)). What that means, in particular, is not relevant to us right now, just understand that it’s r with extra effects tacked on.

Members '[Embed IO, Final IO, CacheEff, MetricEff, LogEff] r is equivalent to (Member (Embed IO) r, Member (Final IO) r, ...), it’s just a more convenient way of listing them all.

So, what this whole function does is strip off some of the main effects but requires us to interpret a few other effects afterward. It’s the main interpreter, in a nutshell.

-- snip --
  . useConstantPrefix "!"
-- snip --

-- `useConstantPrefix` has the type:
useConstantPrefix :: Text -> Sem (ParsePrefix ': r) a -> Sem r a

Having this interpreter will strip off the ParsePrefix effect, which will be required when we want to register commands later.

-- snip --
  . useFullContext
-- snip --

-- `useFullContext` has the type:
useFullContext :: Member CacheEff r => Sem (ConstructContext Message FullContext IO () ': r) a -> Sem r a

useConstantPrefix handles the ConstructContext effect, which determines what information we receive when a command is invoked.

-- snip --
  . runMetricsNoop
-- snip --

-- `runMetricsNoop` has the type:
runMetricsNoop :: Sem (MetricEff ': r) a -> Sem r a

runMetricsNoop will strip off the MetricEff effect by ignoring any metrics that were collected. calamity doesn’t provide any other interpreter for the MetricEff effect, but if we wanted to we could write our own. That’s outside the scope of this post, however.

-- snip --
  . runCacheInMemory
-- snip --

-- `runCacheInMemory` has the type:
runCacheInMemory :: Member (Embed IO) r => Sem (CacheEff ': r) a -> Sem r a

runCacheInMemory strips the CacheEff for us by storing the cache in memory. If we wanted to we could write an effect interpreter that stores the cache in a file or database.

-- snip --
  . runDiToIO di
-- snip --

-- `runDiToIO` has the type:
runDiToIO
  :: forall r level msg a.
     Member (Embed IO) r
  => Di level Path msg
  -> Sem (Di level Path msg ': r) a
  -> Sem r a

runDiToIO will interpret our di logging effect. Note that the LogEff effect mentioned earlier is just a type alias for Di Level Path Message, so this is just an interpreter for the LogEff effect.

Our First Event Handler

Let’s create an event handler that will do something wholesome, like react with 😄 on any message containing the string “Haskell”.

-- snip --
$ do
    info @Text "Setting up commands and handlers..."

    react @'MessageCreateEvt $ \(msg, _usr, _member) -> do
      when ("Haskell" `T.isInfixOf` (msg ^. #content)) $
        void . invoke $ CreateReaction msg msg (UnicodeEmoji "😄")

react is a function that registers an event handler.

react
  :: forall (s :: EventType) r.
  (BotC r, ReactConstraints s)
  => (EHType s -> Sem r ())
  -> Sem r (Sem r ())

The type of event we want to handle has to be passed in as a type argument using the TypeApplications extension, which allows us to instantiate type variables to a specific concrete type. calamity provides the EventType datatype which is a simple enumeration, one of the values being MessageCreateEvt. react expects a type variable with the kind EventType, meaning EventType is used as a data-kind. All this means is that the type EventType is promoted from the type level to the kind level.1 Its values, such as MessageCreateEvt, are promoted from the term level to the type level. Just as the type Int has kind Type, the type 'MessageCreateEvt has the kind EventType. Notice the tick mark on 'MessageCreateEvt. This is to differentiate the value MessageCreateEvt from the type. Usually, GHC can infer this without us explicitly specifying it, and indeed here it’s not required, but we’ll leave it in just to be explicit.

Also, note that the effect row that react uses has a BotC constraint which is just an alias for a few other constraints. We won’t go into the details here, but just know that the runBotIO interpreter handles these constraints for us.

react also expects a function as an argument, the handler body. The type of the input to the body depends on the EventType we specified; different types of events have different data associated with them. This is determined by the EHType type family. For those unfamiliar, a type family is essentially a function that operates on types rather than terms. In the case of EHType, it takes a type with kind EventType (remember, DataKinds promotes EventType to the kind level) and gives us a type. So in our case, EHType 'MessageCreateEvt = (Message, Maybe User, Maybe Member). That means our event handler’s body should have the type (Message, Maybe User, Maybe Member) -> Sem r (), although we’ll only be using the Message portion of that tuple. You can verify this in a GHCi session (by running cabal repl in the terminal) with the command :kind! EHType 'MessageCreateEvt which will tell you the kind of the argument and will also attempt to evaluate it.

λ> :kind! EHType MessageCreateEvt 
EHType MessageCreateEvt :: *
= (Message, Maybe User, Maybe Member)

So for the actual body, we want to take the message and perform an action conditional on the message’s content. We use the when function from Control.Monad, which conditionally performs a monadic/applicative action.

when :: Applicative f => Bool -> f () -> f ()

To access the message’s content we use generic-lens to view the content field of the message (remember that (^.) is just the infix counterpart to view).

To create the action, we’ll need to create a “create reaction” request, specifically a ChannelRequest.

CreateReaction
  :: (HasID Channel c, HasID Message m)
  => c
  -> m
  -> RawEmoji
  -> ChannelRequest ()

CreateReaction is polymorphic in its first two arguments. Rather than requiring a concrete Snowflake for the channel and message to react to, which, it only requires that it’s possible to extract a Snowflake from the inputs. It does this via a typeclass, HasID, which has two type parameters- the type of the Snowflake we wish to extract and the type of the thing to extract from. It has a single method, HasID b a => getID :: a -> Snowflake b. If we look at the instances for HasID we see that there are indeed instances HasID Channel Message and HasID Message Message. To illustrate the convenience that this technique gives us, this is what our handler would look like if CreateReaction required concrete Snowflakes.

-- snip --
void . invoke $ CreateReaction (msg ^. #channelID) (msg ^. #id) (UnicodeEmoji "😄")

Okay, so now that we have our ChannelRequest we can use the invoke function to run it.

invoke
  :: (BotC r, Request a, FromJSON (Result a))
  => a
  -> Sem r (Either RestError (Result a))

Here, Request is a typeclass for which every ChannelRequest a has an instance, and Result is a type family which extracts the type a from a ChannelRequest a.

In our case, since we don’t need the result of the request, we can discard it using the void function from Control.Monad.

void :: Functor f => f a -> f ()

One last thing to note about react is that it returns an action that you can use to unregister it, hence the output being Sem r (Sem r ()).

That’s it! That’s our event handler. You can try it out yourself by putting your bot token in the runBotIO interpreter and running the project.

Adding a command

Let’s add a command to enable (or disable) slow mode at a given duration, optionally specifying a channel, defaulting to the channel the command was invoked in.

Luckily for us, calamity provides a handy DSL for creating commands.

-- snip --
        void . invoke $ CreateReaction msg msg (UnicodeEmoji "😄")

    addCommands $ do
      helpCommand
      command @'[Int, Maybe GuildChannel] "slowmode" $ \ctx seconds mchan -> do
        let cid = maybe (ctx ^. #channel . to getID) getID mchan :: Snowflake Channel
        void . invoke $ ModifyChannel cid $ def
          & #rateLimitPerUser ?~ seconds
        void . invoke $
          CreateReaction (ctx ^. #channel) (ctx ^. #message) (UnicodeEmoji "✅")

Registering commands is done with the addCommands function.

addCommands
  :: (BotC r, Member ParsePrefix r)
  => Sem (DSLState r) a
  -> Sem r (Sem r (), CommandHandler, a)

It constructs the commands and registers the proper event handlers to handle them. It requires the ParsePrefix effect to be present in the effect row. It also allows extra effects in the input’s effect row which are used to track the state of the command DSL, using the type alias DSLState. It yields an action to unregister the event handlers, and an object representing the commands that were registered.

helpCommand will add a default help command in the DSL.

To create a command, we use the command function

command
  :: forall ps r.
  (Member (Final IO) r, TypedCommandC ps r)
  => Text
  -> (Context -> CommandForParsers ps r)
  -> Sem (DSLState r) Command

command takes a command name and a command body and adds a command in the DSL. It also takes a type-level list of command arguments, which it uses to parse the inputs and compute the type of the command body.

In our case, we pass the type-level list '[Int, Maybe GuildChannel] (using TypeApplications) which means our command requires an Int and optionally a GuildChannel.

The body of the command will take a Context and any type parameters we pass in will also be the types of arguments to the body (computed by the CommandForParsers type family).

We use the maybe function to get a default channel id- either the id of the channel provided or the id of the channel the message was invoked in, which is extracted from the Context. We need the id specifically even though the ModifyChannel request only requires something which has a HasID Channel instance, since maybe requires the output types to match up.

We invoke the ModifyChannel request.

ModifyChannel
  :: HasID Channel c
  => c
  -> ChannelUpdate
  -> ChannelRequest Channel

It requires a ChannelUpdate as input.

data ChannelUpdate = ChannelUpdate
  { name :: Maybe Text
  , position :: Maybe Int
  , topic :: Maybe Text
  , nsfw :: Maybe Bool
  , rateLimitPerUser :: Maybe Int
  , bitrate :: Maybe Int
  , userLimit :: Maybe Int
  , permissionOverwrites :: Maybe [Overwrite]
  , parentID :: Maybe (Snowflake Channel)
  }

In our case, we just need the rateLimitPerUser field. Luckily, ChannelUpdate implements the Default typeclass, and so it provides a default value def in which all the fields are set to Nothing. We can then use lens to update just the field we need. We can use the (?~) operator, which is a convenience function that sets a field to Just the value on the right-hand side.

We also react to the command invocation, just like we did in our event handler, this time using the Context instead of a Message.

The parser for the command is quite intelligent, so when we come to run the command, we can pass in either a link to the channel (ala #channel-name) or the id of the channel.

Creating Messages with Ease Using the tell Function

calamity has a typeclass called Tellable, which has a method getChannel.

getChannel 
  :: (BotC r, Member (Error RestError) r) 
  => a 
  -> Sem r (Snowflake Channel)

Any type which has an instance of Tellable can be sent a message with the tell function.

tell 
  :: forall msg r t. 
  (BotC r, ToMessage msg, Tellable t) 
  => t 
  -> msg 
  -> Sem r (Either RestError Message)

It also requires the item being sent to have a ToMessage instance. Many types have this instance, among them the various string types, files, embeds, and mentions.

Let’s create an event handler that responds to any message edit with “Hey! I saw that!”.

-- snip --
    react @'MessageUpdateEvt $ \(_oldMsg, newMsg, _user, _member) -> do
      void . tell @Text newMsg $ "Hey! I saw that!"
-- snip --

Another useful function to check out is reply, which will use Discord’s reply system to reply to a message.

Supercharge your Snowflakes with upgrade

It can be a hassle to get a value if you only have access to its id. calamity provides us with the Upgradable typeclass, which provides the upgrade method.

class Upgradeable a ids | a -> ids, ids -> a where
  upgrade :: BotC r => ids -> P.Sem r (Maybe a)

upgrade will take your id(s) and search the cache for the corresponding value, making a request if it’s not in the cache. There are several useful instances defined, all of which take one or a pair of Snowflakes and provide a complete value.

 Upgradeable GuildChannel (Snowflake GuildChannel) 
 Upgradeable Member (Snowflake Guild, Snowflake Member)

Utilities

Calamity.Utils provides many useful functions: permissions calculations, message formatting, and colors for custom embeds. It’s worthwhile to check it out.

In Summary

There are many things we didn’t get to cover in this post. We only scratched the surface of the commands DSL, we didn’t cover metrics collection, presences, nor the countless datatypes that are defined to model the Discord API. We also didn’t cover most of the effects available in the polysemy library, which could come in handy for storing configuration data, state, etc. But that’s where the documentation comes in. If you’re new to developing real-world Haskell programs, learning how to read the haddocks is invaluable. (A tip: Don’t forget to read the instances!)

If there’s further interest in this I may be inclined to write another post where I write a more fully-featured bot and step through the process, involving other libraries like aeson and database libraries, and defining our own polysemy effects and effect interpreters.

The full source code for the bot is available here.