module System where import qualified Data.Map as M import Control.Monad.Reader import System.IO import Data.List import API plugin :: InfinityPlugin plugin = InfinityPlugin { name = "System", commands = [("join","joins a channel") ,("part","parts a channel") ,("list","list commands") ,("help","shows help for a command") ,("version","show version info")], action = system } system :: PLUGIN system user channel command args = do case command of "join" -> do admins <- asks admins if user `elem` admins then case args of Nothing -> retJust $ "Need a channel..." Just av -> do mapM_ (send "JOIN") (words av) retJust $ "joined " ++ (concat $ intersperse " " $ words av) else retJust "Can't do that..." "part" -> do admins <- asks admins if user `elem` admins then case args of Nothing -> send "PART" channel >> retNothing Just av -> do mapM_ (\ch -> send "PART" ch) (words av) retJust $ "parted " ++ (concat $ intersperse " " $ words av) else retJust "Can't do that..." "list" -> do plist <- getplugs let plist' = map (\p -> ((name p)++" provides: "++(concat . (intersperse " ") . fst . unzip . commands $ p))) plist retJust $ unlines plist' "help" -> do plist <- getplugs case args of Nothing -> retJust $ "Need a command, try '!help help!" Just av -> do let cmd = (head . words) av plist' = filter (\p -> cmd `elem` (fst . unzip . commands $ p)) plist if null plist' then do retJust $ "No plugin with command '"++cmd++"' found..." else do let x = head plist' retJust $ M.findWithDefault "No help available..." cmd $ (M.fromList . commands) x "version" -> infinityVer >>= retJust