File: Channels.hs

package info (click to toggle)
haskell-ircbot 0.6.6.1-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 144 kB
  • sloc: haskell: 881; makefile: 2
file content (38 lines) | stat: -rw-r--r-- 1,414 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
{-# LANGUAGE OverloadedStrings #-}
module Network.IRC.Bot.Part.Channels where

import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TVar (TVar, newTVar, readTVar, writeTVar)
import Control.Monad.Trans (MonadIO(liftIO))
import Data.Monoid ((<>))
import Data.Set (Set, insert, toList)
import Data.ByteString (ByteString)
import Network.IRC (Message(..), joinChan)
import Network.IRC.Bot.BotMonad (BotMonad(..))
import Network.IRC.Bot.Log (LogLevel(..))

initChannelsPart :: (BotMonad m) => Set ByteString -> IO (TVar (Set ByteString), m ())
initChannelsPart chans =
    do channels <- atomically $ newTVar chans
       return (channels, channelsPart channels)

channelsPart :: (BotMonad m) => TVar (Set ByteString) -> m ()
channelsPart channels =
    do msg <- askMessage
       let cmd = msg_command msg
       case cmd of
         "005" -> do chans <- liftIO $ atomically $ readTVar channels
                     mapM_ doJoin (toList chans)
         _ -> return ()
    where
      doJoin :: (BotMonad m) => ByteString -> m ()
      doJoin chan =
          do sendMessage (joinChan chan)
             logM Normal $ "Joining room " <> chan

joinChannel :: (BotMonad m) => ByteString -> TVar (Set ByteString) -> m ()
joinChannel chan channels =
    do liftIO $ atomically $
           do cs <- readTVar channels
              writeTVar channels (insert chan cs)
       sendMessage (joinChan chan)