| Safe Haskell | None |
|---|
Network.Haskbot.Plugin
Contents
Description
The recommended process for exporting plugins is to create a new module
that exports a single function currying the first three arguments to
Plugin. The remaining argument, the Slack secret token, can be
supplied in a separate file exporting the list of installed commands for
Haskbot. This enables you to recreate a registry of installed tokens and
corresponding secret tokens in a separate file outside of version control.
A basic Hello World plugin can be created via:
{-# LANGUAGE OverloadedStrings #-}
module MyPlugins.HelloWorld (register) where
import Data.Text
import Network.Haskbot.Plugin
import Network.Haskbot.Types
name :: Command
name = setCommand "hello_world"
helpText :: Text
helpText = "Have Haskbot say _Hello, World!_ in your current channel."
handler :: HandlerFn
handler slashCom = return $ replySameChan slashCom "Hello, World!"
register :: Text -> Plugin
register = Plugin name helpText handler . setToken
To run the plugin, create a new Slack slash command integration
corresponding to the command /hello_world that points to your Haskbot
server. Add the plugin's register function to your Haskbot server's
plugin registry like detailed in Network.Haskbot, giving it the Slack
integration's secret token as the remaining argument. Rebuild and run the
server. Typing /hello_word into any Slack channel should return a
Haskbot response of Hello, world!
- data Plugin = Plugin {}
- type HandlerFn = SlashCom -> HaskbotM (Maybe Incoming)
- replySameChan :: SlashCom -> Text -> Maybe Incoming
- replyAsDM :: SlashCom -> Text -> Maybe Incoming
- runPlugin :: Plugin -> SlashCom -> HaskbotM ()
- isAuthorized :: Plugin -> SlashCom -> Bool
- selectFrom :: [Plugin] -> Command -> Maybe Plugin
The Plugin type
Constructors
| Plugin | |
Fields
| |
type HandlerFn = SlashCom -> HaskbotM (Maybe Incoming)Source
The type of function run by a plugin. It receives the full Network.Haskbot.SlashCommand invoked and can optionally return a Network.Haskbot.Incoming reply
Common Slack replies
replySameChan :: SlashCom -> Text -> Maybe IncomingSource
Send a Slack reply to the same channel as where the corresponding /slash command/ was invoked, formatted according to Slack
replyAsDM :: SlashCom -> Text -> Maybe IncomingSource
Send a Slack reply as a DM to the user who invoked the slash command, formatted according to Slack
isAuthorized :: Plugin -> SlashCom -> BoolSource