summaryrefslogtreecommitdiff
path: root/Plugins
diff options
context:
space:
mode:
Diffstat (limited to 'Plugins')
-rw-r--r--Plugins/Core.hs61
-rw-r--r--Plugins/Ping.hs31
-rw-r--r--Plugins/Quote.hs158
3 files changed, 0 insertions, 250 deletions
diff --git a/Plugins/Core.hs b/Plugins/Core.hs
deleted file mode 100644
index f81f4bf..0000000
--- a/Plugins/Core.hs
+++ /dev/null
@@ -1,61 +0,0 @@
-module Plugins.Core
- ( mainCore
- ) where
-
-import Control.Concurrent.Chan(Chan)
-import Control.Exception
-import Control.Monad.State
-import Prelude hiding (catch)
-
-import Hsbot.IRCPlugin
-import Hsbot.Types
-import Hsbot.Utils
-
--- | The plugin's main entry point
-mainCore :: Chan BotMsg -> Chan BotMsg -> IO ()
-mainCore serverChan chan = do
- let plugin = PluginState "Core" serverChan chan
- evalStateT (mapM_ sendRegisterCommand ["list", "load", "reload", "unload"]) plugin
- plugin' <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin)
- evalStateT (mapM_ sendUnregisterCommand ["list", "load", "reload", "unload"]) plugin'
-
--- | The IrcPlugin monad main function
-run :: IrcPlugin ()
-run = forever $ do
- msg <- readMsg
- eval msg
- where
- eval :: BotMsg -> IrcPlugin ()
- eval (InternalCmd intCmd) = do
- let request = intCmdBotMsg intCmd
- case intCmdCmd intCmd of
- "RUN" -> let stuff = words $ intCmdMsg intCmd
- in case head stuff of
- "list" -> listPlugins request
- "load" -> loadPlugin $ tail stuff
- "reload" -> reloadPlugin $ tail stuff
- "unload" -> unloadPlugin $ tail stuff
- _ -> lift . trace $ show intCmd -- TODO : help message
- "ANSWER" -> let stuff = intCmdMsg intCmd
- in answerMsg request ("Loaded plugins : " ++ stuff)
- _ -> lift . trace $ show intCmd
- eval (InputMsg _) = return ()
- eval _ = return ()
-
--- | The list command
-listPlugins :: IrcMsg -> IrcPlugin ()
-listPlugins request = do
- sendCommandWithRequest "LIST" "CORE" (unwords []) request
-
--- | The load command
-loadPlugin :: [String] -> IrcPlugin ()
-loadPlugin pluginNames = mapM_ (sendCommand "LOAD" "CORE") pluginNames
-
--- | The reload command
-reloadPlugin :: [String] -> IrcPlugin ()
-reloadPlugin pluginNames = mapM_ (sendCommand "RELOAD" "CORE") pluginNames
-
--- | The unload command
-unloadPlugin :: [String] -> IrcPlugin ()
-unloadPlugin pluginNames = mapM_ (sendCommand "UNLOAD" "CORE") pluginNames
-
diff --git a/Plugins/Ping.hs b/Plugins/Ping.hs
deleted file mode 100644
index 5da3f2f..0000000
--- a/Plugins/Ping.hs
+++ /dev/null
@@ -1,31 +0,0 @@
-module Plugins.Ping
- ( mainPing
- ) where
-
-import Control.Concurrent.Chan
-import Control.Exception
-import Control.Monad.State
-import Prelude hiding (catch)
-
-import Hsbot.IRCPlugin
-import Hsbot.Types
-
--- | The plugin's main entry point
-mainPing :: Chan BotMsg -> Chan BotMsg -> IO ()
-mainPing serverChan chan = do
- let plugin = PluginState "Ping" serverChan chan
- _ <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin)
- return ()
-
--- | The IrcPlugin monad main function
-run :: IrcPlugin ()
-run = forever $ do
- msg <- readMsg
- eval msg
- where
- eval :: BotMsg -> IrcPlugin ()
- eval (InputMsg msg)
- | (command msg) == "PING" = writeMsg $ OutputMsg $ IrcMsg Nothing "PONG" (parameters msg)
- | otherwise = return ()
- eval _ = return ()
-
diff --git a/Plugins/Quote.hs b/Plugins/Quote.hs
deleted file mode 100644
index 61e4558..0000000
--- a/Plugins/Quote.hs
+++ /dev/null
@@ -1,158 +0,0 @@
-module Plugins.Quote
- ( mainQuote
- ) where
-
-import Control.Concurrent.Chan
-import Control.Exception
-import Control.Monad.State
-import qualified Data.Map as M
-import Data.Maybe(fromMaybe)
-import qualified Data.Text as T
-import qualified Data.Text.IO as TIO
-import Data.Time
-import IO hiding (catch)
-import Prelude hiding (catch)
-import System.Random(randomRIO)
-
-import Hsbot.IRCPlugin
-import Hsbot.Types
-import Hsbot.Utils
-
--- | A quote element
-data QuoteElt = QuoteElt
- { eltQuoter :: String
- , eltQuote :: String
- } deriving (Read, Show)
-
--- | A quote object
-data Quote = Quote
- { quoter :: String
- , quote :: [QuoteElt]
- , quoteTime :: UTCTime
- , votes :: Int
- } deriving (Read, Show)
-
--- | A QuoteBot state
-data QuoteBotState = QuoteBotState
- { nextQuoteId :: Integer
- , quoteBotDB :: M.Map Integer Quote
- , quotesInProgress :: M.Map Integer Quote
- } deriving (Read, Show)
-
--- | The QuoteBot monad
-type QuoteBot a = StateT QuoteBotState (StateT PluginState IO) a
-
--- | The plugin's main entry point
-mainQuote :: Chan BotMsg -> Chan BotMsg -> IO ()
-mainQuote serverChan chan = do
- -- First of all we restore the database
- txtQuoteBot <- TIO.readFile $ "quotedb.txt"
- let quoteBot = read (T.unpack txtQuoteBot) :: QuoteBotState
- -- The plugin main loop
- let plugin = PluginState "Quote" serverChan chan
- evalStateT (mapM_ sendRegisterCommand ["quote"]) plugin
- _ <- (evalStateT (run quoteBot) plugin) `catch` (\(_ :: AsyncException) -> return quoteBot)
- evalStateT (mapM_ sendUnregisterCommand ["quote"]) plugin
-
--- | The IrcPlugin monad main function
-run :: QuoteBotState -> IrcPlugin (QuoteBotState)
-run quoteBot = do
- msg <- readMsg
- quoteBot' <- eval msg
- run quoteBot'
- where
- -- | evaluate what we just received
- eval :: BotMsg -> IrcPlugin (QuoteBotState)
- eval (InternalCmd intCmd)
- | intCmdCmd intCmd == "RUN" = do
- quoteBot' <- execStateT (runCommand intCmd) quoteBot
- return quoteBot'
- | otherwise = do
- lift . trace $ show intCmd
- return quoteBot
- eval (InputMsg _) = return (quoteBot)
- eval _ = return (quoteBot)
-
--- | run a command we received
-runCommand :: IntCmd -> QuoteBot ()
-runCommand intCmd
- | theCommand == "quote" = runQuoteCommand
- | otherwise = do
- lift . lift . trace $ show intCmd -- TODO : help message
- where
- -- | the message is a quote command
- runQuoteCommand :: QuoteBot ()
- | length args == 0 = do
- quoteDB <- gets quoteBotDB
- x <- liftIO $ randomRIO (0, (length $ M.keys quoteDB) - 1)
- mapM_ (lift . answerMsg request) (formatQuote (M.keys quoteDB !! x) (M.elems quoteDB !! x))
- | otherwise = do
- dispatchQuoteCmd $ head args
- -- | quote command dispatcher
- dispatchQuoteCmd :: String -> QuoteBot ()
- dispatchQuoteCmd cmd
- | cmd == "start" = do
- quoteBot <- get
- now <- liftIO $ getCurrentTime
- let sender = takeWhile (/= '!') $ fromMaybe "ARGH" (prefix request)
- newQuote = Quote sender [(quoteElt stuff)] now 0
- quoteId = nextQuoteId quoteBot
- quotesInProgress' = M.insert quoteId newQuote (quotesInProgress quoteBot)
- put $ quoteBot { nextQuoteId = quoteId + 1, quotesInProgress = quotesInProgress' }
- lift $ answerMsg request ("New quoteId : " ++ show quoteId)
- syncQuoteBot
- | cmd == "append" = do
- quoteBot <- get
- case reads (head stuff) of
- [(quoteId :: Integer,"")] -> do
- case M.lookup quoteId (quotesInProgress quoteBot) of
- Just theQuote -> do
- let newQuote = theQuote { quote = (quoteElt $ tail stuff) : (quote theQuote) }
- quotesInProgress' = M.insert quoteId newQuote (quotesInProgress quoteBot)
- put $ quoteBot { quotesInProgress = quotesInProgress' }
- syncQuoteBot
- Nothing -> lift $ answerMsg request ("quoteId not found : " ++ (show quoteId))
- _ -> lift $ answerMsg request ("Invalid quoteId : " ++ (head stuff))
- | cmd == "commit" = do
- quoteBot <- get
- case reads (head stuff) of
- [(quoteId :: Integer,"")] -> do
- case M.lookup quoteId (quotesInProgress quoteBot) of
- Just theQuote -> do
- let quoteBotDB' = M.insert quoteId theQuote (quoteBotDB quoteBot)
- quotesInProgress' = M.delete quoteId (quotesInProgress quoteBot)
- put $ quoteBot { quoteBotDB = quoteBotDB', quotesInProgress = quotesInProgress' }
- syncQuoteBot
- Nothing -> lift $ answerMsg request ("quoteId not found : " ++ (show quoteId))
- _ -> lift $ answerMsg request ("Invalid quoteId : " ++ (head stuff))
- -- | cmd == "abort" =
- | otherwise = lift $ answerMsg request ("Invalid command : " ++ cmd)
- -- | Gets the new QuoteElt
- quoteElt :: [String] -> QuoteElt
- quoteElt msg = do
- let budy = head $ msg
- theQuote = unwords . tail $ msg
- QuoteElt budy theQuote
- -- | utilities
- params = words . intCmdMsg $ intCmd
- theCommand = head params
- args = tail params
- stuff = tail args
- request = intCmdBotMsg intCmd
-
--- | The function that sync the quoteDB on disk
-syncQuoteBot :: QuoteBot ()
-syncQuoteBot = do
- quoteBot <- get
- file' <- liftIO $ openFile "quotedb.txt" WriteMode
- liftIO . hPutStr file' $ show quoteBot
- liftIO $ hClose file'
-
-formatQuote :: Integer -> Quote -> [String]
-formatQuote quoteId theQuote =
- ("+---| " ++ (show quoteId) ++ " |-- Reported by " ++ (quoter theQuote) ++ " on " ++ (show $ quoteTime theQuote)) :
- foldl (\acc x -> formatQuoteElt x : acc) ["`------------------------------------------"] (quote theQuote)
- where
- formatQuoteElt :: QuoteElt -> String
- formatQuoteElt quoteElt = "| <" ++ (eltQuoter quoteElt) ++ "> " ++ (eltQuote quoteElt)
-