aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--src/IRC.hs181
-rw-r--r--src/Lib.hs48
-rw-r--r--src/Plugin/Help.hs2
3 files changed, 137 insertions, 94 deletions
diff --git a/src/IRC.hs b/src/IRC.hs
index 18508b2..b0a623b 100644
--- a/src/IRC.hs
+++ b/src/IRC.hs
@@ -1,95 +1,96 @@
{-# LANGUAGE OverloadedStrings #-}
module IRC
- ( connectIRC
+ ( -- connectIRC
) where
-import Control.Monad (sequence_)
-import Control.Monad.IO.Class (liftIO)
-import Control.Monad.Trans.Class (lift)
-import Control.Monad.Trans.Maybe (MaybeT(MaybeT), runMaybeT)
-import qualified Data.ByteString as B
-import qualified Data.Text as T
-
-import qualified Network.IRC.Client as IRC
-
-import Bot (Bot)
-import Message
-import Plugin (matchPlugin, performPlugin)
-import Plugin.Base (queryOnly)
-
-connectIRC :: B.ByteString -> Int -> T.Text -> IO ()
-connectIRC host port nick = do
- conn <- IRC.connectWithTLS host port 0.2
- let cfg = IRC.defaultIRCConf nick
- let cfg' = cfg
- {
- IRC._eventHandlers = handlePrivmsg : IRC._eventHandlers cfg
- , IRC._channels = ["#test-chan-13513"]
- }
- IRC.start conn cfg'
-
-handlePrivmsg :: IRC.EventHandler s
-handlePrivmsg = IRC.EventHandler
- { IRC._description = ""
- , IRC._matchType = IRC.EPrivmsg
- , IRC._eventFunc = \evt -> dispatchEvent evt
- }
- where
- dispatchEvent :: IRC.UnicodeEvent -> IRC.StatefulIRC s ()
- dispatchEvent (IRC.Event _ (IRC.User nick) (IRC.Privmsg _ (Right msg))) = do
- let message = Message
- { text = msg
- , channel = nick
- , nick = nick
- }
- response <- lift $ runMaybeT $ privmsgFromPlugin message
- case response of
- Nothing -> return ()
- Just r -> sequence_ r
- dispatchEvent (IRC.Event
- _ (IRC.Channel chan nick) (IRC.Privmsg _ (Right msg))) = do
- let message = Message
- { text = msg
- , channel = chan
- , nick = nick
- }
- case messageForBot message of
- Nothing -> return ()
- Just message -> do
- response <- lift $ runMaybeT $ privmsgFromPlugin message
- case response of
- Nothing -> return ()
- Just r -> sequence_ r
-
-privmsgFromPlugin :: Message -> MaybeT Bot [IRC.StatefulIRC s ()]
-privmsgFromPlugin message = do
- plugin <- liftMaybe $ matchPlugin message
- response <- lift $ performPlugin plugin message
- -- plugin' <- liftMaybe plugin
- return $ case response of
- Left err -> [IRC.send $ IRC.Privmsg
- (toChannel plugin message)
- (Right err)]
- Right r -> map
- (\r -> IRC.send $ IRC.Privmsg
- (toChannel plugin message)
- (Right r) )
- (splitAtNewlines $ splitLongLines r)
- where
- liftMaybe = MaybeT . return
-
- -- IRC only permits 512 bytes per line. Use less to allow for protocol
- -- information that gets sent in addition to the message content.
- splitLongLines txt = T.chunksOf 400 txt
-
- splitAtNewlines lst = foldr (\s acc -> (T.lines s) ++ acc) [] lst
-
- toChannel plugin message = case queryOnly plugin of
- False -> channel message
- True -> nick message
-
-messageForBot :: Message -> Maybe Message
-messageForBot m = case T.stripPrefix "sorbot: " (text m) of
- Nothing -> Nothing
- Just t -> Just m { text = t }
+-- import Control.Monad (sequence_)
+-- import Control.Monad.IO.Class (liftIO)
+-- import Control.Monad.Trans.Class (lift)
+-- import Control.Monad.Trans.Maybe (MaybeT(MaybeT), runMaybeT)
+-- import qualified Data.ByteString as B
+-- import qualified Data.Text as T
+--
+-- import qualified Network.IRC.Client as IRC
+--
+-- -- import Bot (Bot)
+-- import Bot (Bot, runBot)
+-- import Message
+-- import Plugin (matchPlugin, performPlugin)
+-- import Plugin.Base (queryOnly)
+--
+-- connectIRC :: B.ByteString -> Int -> T.Text -> IO ()
+-- connectIRC host port nick = do
+-- conn <- IRC.connectWithTLS host port 0.2
+-- let cfg = IRC.defaultIRCConf nick
+-- let cfg' = cfg
+-- {
+-- IRC._eventHandlers = handlePrivmsg : IRC._eventHandlers cfg
+-- , IRC._channels = ["#test-chan-13513"]
+-- }
+-- IRC.start conn cfg'
+--
+-- handlePrivmsg :: IRC.EventHandler s
+-- handlePrivmsg = IRC.EventHandler
+-- { IRC._description = ""
+-- , IRC._matchType = IRC.EPrivmsg
+-- , IRC._eventFunc = \evt -> dispatchEvent evt
+-- }
+-- where
+-- dispatchEvent :: IRC.UnicodeEvent -> IRC.StatefulIRC s ()
+-- dispatchEvent (IRC.Event _ (IRC.User nick) (IRC.Privmsg _ (Right msg))) = do
+-- let message = Message
+-- { text = msg
+-- , channel = nick
+-- , nick = nick
+-- }
+-- response <- lift $ runMaybeT $ privmsgFromPlugin message
+-- case response of
+-- Nothing -> return ()
+-- Just r -> sequence_ r
+-- dispatchEvent (IRC.Event
+-- _ (IRC.Channel chan nick) (IRC.Privmsg _ (Right msg))) = do
+-- let message = Message
+-- { text = msg
+-- , channel = chan
+-- , nick = nick
+-- }
+-- case messageForBot message of
+-- Nothing -> return ()
+-- Just message -> do
+-- response <- lift $ runMaybeT $ privmsgFromPlugin message
+-- case response of
+-- Nothing -> return ()
+-- Just r -> sequence_ r
+--
+-- privmsgFromPlugin :: Message -> MaybeT Bot [IRC.StatefulIRC s ()]
+-- privmsgFromPlugin message = do
+-- plugin <- liftMaybe $ matchPlugin message
+-- response <- lift $ performPlugin plugin message
+-- -- plugin' <- liftMaybe plugin
+-- return $ case response of
+-- Left err -> [IRC.send $ IRC.Privmsg
+-- (toChannel plugin message)
+-- (Right err)]
+-- Right r -> map
+-- (\r -> IRC.send $ IRC.Privmsg
+-- (toChannel plugin message)
+-- (Right r) )
+-- (splitAtNewlines $ splitLongLines r)
+-- where
+-- liftMaybe = MaybeT . return
+--
+-- -- IRC only permits 512 bytes per line. Use less to allow for protocol
+-- -- information that gets sent in addition to the message content.
+-- splitLongLines txt = T.chunksOf 400 txt
+--
+-- splitAtNewlines lst = foldr (\s acc -> (T.lines s) ++ acc) [] lst
+--
+-- toChannel plugin message = case queryOnly plugin of
+-- False -> channel message
+-- True -> nick message
+--
+-- messageForBot :: Message -> Maybe Message
+-- messageForBot m = case T.stripPrefix "sorbot: " (text m) of
+-- Nothing -> Nothing
+-- Just t -> Just m { text = t }
diff --git a/src/Lib.hs b/src/Lib.hs
index 3d875ef..821a49b 100644
--- a/src/Lib.hs
+++ b/src/Lib.hs
@@ -6,12 +6,52 @@ module Lib
import Database.SQLite.Simple
+import Bot (Bot(runBot))
import CliOptions (Options(language), parseOptions)
-import IRC (connectIRC)
+-- import IRC (connectIRC)
import Message
-import Plugin
+-- import Plugin
+import Plugin.Base (Plugin)
+import PluginList as PL (plugins)
+-- TODO: tmp test
+import Control.Monad.Reader (runReaderT)
+import CliOptions (Options(..))
+import Plugin.Help as Help (help)
+import I18n (Locale(EN))
+import Plugin (performPlugin)
+import qualified Data.Text.IO as TIO
someFunc :: IO ()
someFunc = do
- options <- parseOptions
- connectIRC "irc.freenode.net" 6697 "test-bot-7890asdf"
+ -- options <- parseOptions
+ -- halp <- runReaderT (runBot Help.help) Options
+ -- { slackApiToken = "booya"
+ -- , language = EN
+ -- }
+ -- case performPlugin halp "hello" of
+ -- Left s -> TIO.putStrLn s
+ -- Right s -> TIO.putStrLn s
+
+ -- halp <- performPlugin Help.help "_msg"
+ hilp <- runReaderT
+ (runBot
+ (performPlugin Help.help Message
+ { text = "_msg"
+ , channel = "#?"
+ , nick = "zyx"
+ }))
+ Options
+ { slackApiToken = "booya"
+ , language = EN
+ }
+ case hilp of
+ Left x -> TIO.putStrLn x
+ Right x -> TIO.putStrLn x
+
+ -- connectIRC "irc.freenode.net" 6697 "test-bot-7890asdf"
+
+initializePlugins :: Options -> [IO Plugin]
+initializePlugins options =
+ map
+ (\p -> runReaderT (runBot p) options)
+ plugins
diff --git a/src/Plugin/Help.hs b/src/Plugin/Help.hs
index ebe3760..7694e87 100644
--- a/src/Plugin/Help.hs
+++ b/src/Plugin/Help.hs
@@ -32,5 +32,7 @@ helpAction _ = do
where
longestCommandLen plugins = foldr (max) 0 (map (T.length . command) plugins)
+-- TODO: Build a new plugin list _in the help plugin_ that applies Config to a
+-- list of plugins and uses that to render the text
plugins :: [Bot Plugin]
plugins = PL.plugins ++ [help]