Tutorial · hlian/linklater Wiki · GitHub
Skip to content
Hao Lian edited this page May 11, 2017 · 10 revisions

Authentication

With this we are ready to create our prize-winning robot. In this tutorial we will build out a real-time messaging robot on Slack, a computer program masquerading as a regular Slack user that people will be able to invite and talk to. First we will need to authenticate with Slack:

import Control.Lens hiding ((.=))
import Data.Aeson
import Network.Wreq
import URI.ByteString

u :: String -> String
u = ("https://slack.com" ++)

data World = World { _wss :: !URI } deriving (Show)

instance FromJSON World where
  parseJSON (Object o) = do
    ok <- o .: "ok"
    url <- o .: "url"
    guard ok
    let parsed = parseURI strictURIParserOptions (url ^. re utf8)
    either (fail . show) (return . World) parsed

startRTM :: Text -> IO World
startRTM apiToken = do
  -- (1)
  let opts = defaults & param "token" .~ [apiToken]
                      & param "simple_latest" .~ ["1"]
                      & param "no_unreads" .~ ["1"]
  -- (2)
  resp <- getWith opts (u "/api/rtm.start")
  -- (3)
  case eitherDecode (resp ^. responseBody) of
    Right world ->
      return (_wss world)
    Left err ->
      error err

(1) Here we construct a Wreq request with token=$token&simple_latest=1&no_unreads=1 as our querystring.

(2) A request is made. Bytes zip along aging American infrastructure.

(3) We use Aeson to decode the JSON response, grabbing the WebSocket URL out of the wss field.

This helper function is packaged up as startRTM in Network.Linklater so no need to copy and paste, hopefully. The actual type signature is a little more polymorphic, a little less friendly.

Channels

We now would like to set up an "inbox" channel, where we place incoming messages from the WebSocket, and an "outbox" channel, where we write outgoing messages to. There are lots of ways to do this, but an easy "get things done quickly" choice would be unbounded channels from Control.Concurrent.Chan.

import qualified Network.WebSockets as Sock
import Control.Concurrent.Chan
import Control.Lens
import Data.Text.Strict.Lens

data Speech = Speech { _replyTo :: !Line, _t :: !Text } deriving (Show)
data Speech' = Speech' { _speech :: !Speech, _id :: !Int } deriving (Show)

instance ToJSON Speech' where
  toJSON (Speech' (Speech line t) id_) =
    object [ "id" .= id_
           , "channel" .= (line ^. channel)
           , "text" .= t
           , "type" .= ("message" :: String)
           ]

voila :: URI -> Chan Speech -> IO (Chan Bytes)
voila uri outbox =
  case (uri ^? authorityL . _Just . authorityHostL . hostBSL . utf8 . unpacked,
        uri ^? pathL . utf8 . unpacked) of
    (Just host, Just path) -> do
      chan <- newChan
      Sock.runSecureClient host 443 path (consumer chan)
      -- (1)
      return chan
    _ ->
      error ("invalid url: " <> show uri)
  where
    consumer chan conn = do
      void $ forkIO (forever worker)
      void $ forkIO (forever listener)
      where
        worker = do
          -- (2)
          msg <- Sock.receiveData conn
          writeChan chan msg
        listener = do
          -- (3)
          speech <- readChan outbox
          Sock.sendTextData conn (encode (Speech' speech 1))

This function takes the WebSocket URL from above and connects to it using the lovely wuss package. When messages come in, we write them immediately to the inbox (the channel being returned on line (1)). We simultaneously fork a green thread to continuously read from the outbox (line (2)); when a message arrives we encode it to Slack's JSON schema and write it to the WebSocket (line (3)).

A Jazz-Hands Robot

Here is a robot that screams "JAZZ HANDS" after three usages of the :raised_hands: emoji:

jazzBot :: Chan Bytes -> Chan Speech -> IO ()
jazzBot inbox outbox = do
  -- (1)
  countDB <- newMVar (0 :: Int)
  -- (2)
  withInbox inbox $ \line_ ->
    when (Text.isInfixOf ":raised_hands:" (line_ ^. truth)) $ do
      -- (3)
      let update = (`mod` 3) . (+ 1) &&& id
      count <- modifyMVar countDB (return . update)
      when (count == 2) $
        writeChan outbox (Speech line_  "JAZZ HANDS")

withInbox :: FromJSON a => Chan Bytes -> (a -> IO b) -> IO ()
withInbox inbox cont = do
  chan <- dupChan inbox
  (void . forkIO . forever) $ do
    bytes <- readChan chan
    case eitherDecode (bytes ^. lazy) of
      Left _ ->
        return ()
      Right o ->
        void (cont o)

(1) We set up a small in-memory database, an MVar Int.

(2) We map over incoming messages from the inbox. This is a little more convoluted than you might think, since we need to duplicate the channel (so as to allow other robots to use the same inbox) and decode incoming messages from JSON.

(3) For each usage of :raised_hands: we increment the counter in the database modulo 3. On every third increment we scream JAZZ HANDS into the channel. Note this logic will break down when @jazzbot is invited into multiple channels. We will leave it as a user exercise to make this code understand multiple channels.

Main

Now we can put everything together:

import qualified System.Environment as Env

main :: IO ()
main = void $ do
  Just apiToken <- Env.lookupEnv "API_TOKEN"
  outbox <- newChan
  uri <- startRTM apiToken
  inbox <- voila uri outbox
  jazzChan inbox outbox
  someOtherRobot inbox outbox
  yetMoreRobot inbox outbox
  sinkChan inbox

-- | Empties out the original channel, so as to prevent memory leaks.
sinkChan :: Chan Bytes -> IO ()
sinkChan originalChan =
  (void . forever) $ readChan originalChan

We read the API token from our environment (not great but hey this tutorial can only be so long) and then set up the outbox channel. Each robot is given the same inbox and outbox channel in the hopes that they will all remember to call dupChan when the time comes. We then read off all the messages from the original channel so the garbage collector can free them.

You can find a working version of this code in the examples/ tutorial.

That's all there is to writing a RTM Slackbot!

WHY–THOUGH IN THE EARLY DAYS OF INTERLACE'S INTERNETTED TELEPUTERS THAT OPERATED OFF LARGELY THE SAME FIBER-DIGITAL GRID AS THE PHONE COMPANIES, THE ADVENT OF VIDEO-TELEPHONING (A.K.A. 'VIDEOPHONY') ENJOYED AN INTERVAL OF HUGE CONSUMER POPULARITY–CALLERS THRILLED AT THE IDEA OF PHONE-INTERFACING BOTH AURALLY AND FACIALLY ON FIRST-GENERATION TELEPUTERS THAT AT THAT TIME WERE LITTLE MORE THAN HIGH-TECH TV SETS, THOUGH OF COURSE THEY HAD THAT LITTLE 'INTELLIGENT-AGENT" HOMUNCULAR ICON THAT WOULD APPEAR AT THE LOWER-RIGHT OF A BROADCAST/CABLE PROGRAM AND TELL YOU THE TIME AND TEMPERATURE OUTSIDE OR REMIND YOU TO TAKE YOUR BLOOD-PRESSURE MEDICATION OR ALERT YOU TO A PARTICULARLY COMPELLING ENTERTAINMENT-OPTION NOW COMING UP ON CHANNEL LIKE 491 OR SOMETHING

Clone this wiki locally