calamity: A library for writing discord bots in haskell

[ library, mit, network, web ] [ Propose Tags ]

Please see the README on GitHub at https://github.com/simmsb/calamity#readme


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.2.0, 0.1.3.0, 0.1.3.1, 0.1.4.0, 0.1.4.1, 0.1.4.2, 0.1.4.3, 0.1.4.4, 0.1.5.0, 0.1.5.1, 0.1.6.0, 0.1.6.1, 0.1.6.2, 0.1.7.0, 0.1.8.0, 0.1.8.1, 0.1.9.0, 0.1.9.1, 0.1.9.2, 0.1.9.3, 0.1.9.4, 0.1.10, 0.1.10.1, 0.1.11.0, 0.1.11.1, 0.1.11.2, 0.1.12.0, 0.1.13.0, 0.1.14.0, 0.1.14.1, 0.1.14.2, 0.1.14.3, 0.1.14.4, 0.1.14.5, 0.1.14.6, 0.1.14.7, 0.1.14.8, 0.1.14.9, 0.1.15.0, 0.1.16.0, 0.1.17.0, 0.1.17.1, 0.1.18.0, 0.1.18.1, 0.1.19.0, 0.1.19.1, 0.1.19.2, 0.1.20.0, 0.1.20.1, 0.1.21.0, 0.1.22.0, 0.1.22.1, 0.1.23.0, 0.1.23.1, 0.1.24.0, 0.1.24.1, 0.1.24.2, 0.1.25.0, 0.1.25.1, 0.1.26.0, 0.1.26.1, 0.1.27.0, 0.1.28.0, 0.1.28.1, 0.1.28.2, 0.1.28.3, 0.1.28.4, 0.1.28.5, 0.1.29.0, 0.1.30.0, 0.1.30.1, 0.1.30.2, 0.1.30.3, 0.1.30.4, 0.1.31.0, 0.2.0.0, 0.2.0.2, 0.3.0.0, 0.4.0.0, 0.5.0.0, 0.6.0.0, 0.7.0.0, 0.7.0.1, 0.7.1.0, 0.8.0.0, 0.9.0.0, 0.10.0.0, 0.11.0.0
Change log ChangeLog.md
Dependencies aeson (>=1.4 && <2), async (>=2.2 && <3), base (>=4.12 && <5), bytestring (>=0.10 && <0.12), colour (>=2.3.5 && <2.4), concurrent-extra (>=0.7 && <0.8), connection (>=0.2.6 && <0.4), containers (>=0.6 && <0.7), data-default-class (>=0.1 && <0.2), data-flags (>=0.0.3 && <0.1), deepseq (>=1.4.4.0 && <2), deque (>=0.4 && <0.5), df1 (>=0.3 && <0.5), di-core (>=1.0.4 && <1.1), di-polysemy (>=0.2 && <0.3), exceptions (>=0.10 && <0.11), fmt (>=0.6 && <0.7), focus (>=1.0 && <2), generic-lens (>=2.0 && <3), hashable (>=1.2 && <2), http-api-data (>=0.4.3 && <0.5), http-client (>=0.5 && <0.8), http-date (>=0.0.8 && <0.1), http-types (>=0.12 && <0.13), lens (>=4.18 && <5), lens-aeson (>=1.1 && <2), megaparsec (>=8 && <10), mime-types (>=0.1 && <0.2), mtl (>=2.2 && <3), polysemy (>=1.3 && <2), polysemy-plugin (>=0.2 && <0.4), reflection (>=2.1 && <3), req (>=3.1 && <3.10), safe-exceptions (>=0.1 && <2), scientific (>=0.3 && <0.4), stm (>=2.5 && <3), stm-chans (>=3.0 && <4), stm-containers (>=1.1 && <2), text (>=1.2 && <2), text-show (>=3.8 && <4), time (>=1.8 && <1.12), tls (>=1.4 && <2), typerep-map (>=0.3 && <0.4), unagi-chan (>=0.4 && <0.5), unboxing-vector (>=0.2 && <0.3), unordered-containers (>=0.2 && <0.3), vector (>=0.12 && <0.13), websockets (>=0.12 && <0.13), x509-system (>=1.6.6 && <1.7) [details]
License MIT
Copyright 2020 Ben Simms
Author Ben Simms
Maintainer ben@bensimms.moe
Category Network, Web
Home page https://github.com/simmsb/calamity
Bug tracker https://github.com/simmsb/calamity/issues
Source repo head: git clone https://github.com/simmsb/calamity
Uploaded by nitros12 at 2021-04-12T07:31:38Z
Distributions
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 40098 total (213 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2021-04-12 [all 1 reports]

Readme for calamity-0.1.28.1

[back to package description]

Calamity

Hackage Gitlab pipeline status License Hackage-Deps Discord Invite

Calamity is a Haskell library for writing discord bots, it uses Polysemy as the core library for handling effects, allowing you to pick and choose how to handle certain features of the library.

If you're looking for something with a less complicated interface, you might want to take a look at discord-haskell.

The current customisable effects are:

  • Cache: The default cache handler keeps the cache in memory, however you could write a cache handler that stores cache in a database for example.

  • Metrics: The library has counters, gauges, and histograms installed to measure useful things, by default these are not used (and cost nothing), but could be combined with Prometheus. An example of using prometheus as the metrics handler can be found here.

  • Logging: The di-polysemy library is used to allow the logging effect to be customized, or disabled.

Docs

You can find documentation on hackage at: https://hackage.haskell.org/package/calamity

Examples

Some example projects can be found at:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLabels #-}

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}

{-# LANGUAGE TypeOperators #-}

module Main where

import           Calamity
import           Calamity.Cache.InMemory
import           Calamity.Commands
import qualified Calamity.Commands.Context                  as CommandContext
import           Calamity.Metrics.Noop

import           Control.Concurrent
import           Control.Concurrent.STM.TVar
import           Control.Lens
import           Control.Monad

import           Data.Text.Lazy              ( Text, fromStrict )
import           Data.Text.Strict.Lens

import qualified Di
import qualified DiPolysemy                  as DiP

import qualified Polysemy                    as P
import qualified Polysemy.Async              as P
import qualified Polysemy.AtomicState        as P
import qualified Polysemy.Embed              as P
import qualified Polysemy.Fail               as P

import           Prelude                     hiding ( error )

import           TextShow

data Counter m a where
  GetCounter :: Counter m Int

P.makeSem ''Counter

runCounterAtomic :: P.Member (P.Embed IO) r => P.Sem (Counter ': r) a -> P.Sem r a
runCounterAtomic m = do
  var <- P.embed $ newTVarIO (0 :: Int)
  P.runAtomicStateTVar var $ P.reinterpret (\case
                                              GetCounter -> P.atomicState (\v -> (v + 1, v))) m

handleFailByLogging m = do
  r <- P.runFail m
  case r of
    Left e -> DiP.error (e ^. packed)
    _      -> pure ()

info, debug :: BotC r => Text -> P.Sem r ()
info = DiP.info
debug = DiP.info

tellt :: (BotC r, Tellable t) => t -> Text -> P.Sem r (Either RestError Message)
tellt t m = tell t $ L.toStrict m

main :: IO ()
main = do
  token <- view packed <$> getEnv "BOT_TOKEN"
  Di.new $ \di ->
    void . P.runFinal . P.embedToFinal . DiP.runDiToIO di . runCounterAtomic . runCacheInMemory . runMetricsNoop . useConstantPrefix "!"
      $ runBotIO (BotToken token) defaultIntents $ do
      addCommands $ do
        helpCommand
        command @'[User] "utest" $ \ctx u -> do
          void $ tellt ctx $ "got user: " <> showtl u
        command @'[Named "u" User, Named "u1" User] "utest2" $ \ctx u u1 -> do
          void $ tellt ctx $ "got user: " <> showtl u <> "\nand: " <> showtl u1
        command @'[L.Text, Snowflake User] "test" $ \ctx something aUser -> do
          info $ "something = " <> showt something <> ", aUser = " <> showt aUser
        command @'[] "hello" $ \ctx -> do
          void $ tellt ctx "heya"
        group "testgroup" $ do
          command @'[[L.Text]] "test" $ \ctx l -> do
            void $ tellt ctx ("you sent: " <> showtl l)
          command @'[] "count" $ \ctx -> do
            val <- getCounter
            void $ tellt ctx ("The value is: " <> showtl val)
          group "say" $ do
            command @'[KleenePlusConcat L.Text] "this" $ \ctx msg -> do
              void $ tellt ctx msg
        command @'[Snowflake Emoji] "etest" $ \ctx e -> do
          void $ tellt ctx $ "got emoji: " <> showtl e
        command @'[] "explode" $ \ctx -> do
          Just x <- pure Nothing
          debug "unreachable!"
        command @'[] "bye" $ \ctx -> do
          void $ tellt ctx "bye!"
          stopBot
        command @'[] "fire-evt" $ \ctx -> do
          fire $ customEvt @"my-event" ("aha" :: L.Text, ctx ^. #message)
        command @'[L.Text] "wait-for" $ \ctx s -> do
          void $ tellt ctx ("waiting for !" <> s)
          waitUntil @'MessageCreateEvt (\msg -> msg ^. #content == ("!" <> s))
          void $ tellt ctx ("got !" <> s)
      react @'MessageCreateEvt $ \msg -> handleFailByLogging $ case msg ^. #content of
        "!say hi" -> replicateM_ 3 . P.async $ do
          info "saying heya"
          Right msg' <- tellt msg "heya"
          info "sleeping"
          P.embed $ threadDelay (5 * 1000 * 1000)
          info "slept"
          void . invoke $ EditMessage (msg ^. #channelID) msg' (Just "lol") Nothing
          info "edited"
        _ -> pure ()
      react @('CustomEvt "command-error" (CommandContext.Context, CommandError)) $ \(ctx, e) -> do
        info $ "Command failed with reason: " <> showt e
        case e of
          ParseError n r -> void . tellt ctx $ "Failed to parse parameter: `" <> L.fromStrict n <> "`, with reason: ```\n" <> r <> "```"
      react @('CustomEvt "my-event" (L.Text, Message)) $ \(s, m) ->
        void $ tellt m ("Somebody told me to tell you about: " <> s)

Disabling library logging

The library logs on debug levels by default, if you wish to disable logging you can do something along the lines of:

Di.new $ \di ->
-- ...
  . runDiToIO di
  -- disable logs emitted inside calamity
  . DiPolysemy.local (Di.Core.filter (\_ _ _ -> False))
  . runBotIO -- ...
  -- re-enable logs emitted inside your bot's code
  . DiPolysemy.local (const di)