{-# OPTIONS -fglasgow-exts #-} module Esotericbot.Help where import Data.Attoparsec as A import Data.List.Stream as L import Data.ByteString.Lazy.Char8 as BS import Control.Monad.State import Esotericbot.EBTypes import Esotericbot.BSUtils import Esotericbot.BSH import Esotericbot.IRCCom data BSHit = forall bs . BSHAble bs => BSHit bs instance BSHAble BSHit where send ( BSHit bs ) = send bs get_help h cmds = do let cmd = irc_cmd cmds sb <- get if null_cmd cmd then do avo <- liftIO $ ls2bs 45 "Try 'help' followed by one of the following: "# priv_msg h cmds $ avo `hAppend` L.intersperse ( BSHit ' ' ) ( L.map ( \ l -> BSHit $ prefix l `hAppend` -- this wonky code looks similar to a 'contrived' example of syntax in the Haskell 98 report '/' `hAppend` name l ) $ plugins sb ) maybe ( return ( ) ) ( \ _ -> do chan_help <- liftIO $ ls2bs 128 "If you are an operator for this channel, you can also use the commands 'op enable' and 'op disable' to enable or disable the bot."# priv_msg h cmds chan_help ) $ irc_chan cmds else do either ( const $ do un <- liftIO $ ls2bs 22 "Unrecognized command: "# priv_msg h cmds $ un `hAppend` cmd ) id $ snd $ parse ( get_lang_help h cmds $ plugins sb ) cmd null_cmd = BS.all (==' ') get_lang_help h cmds ls = do spaces choices $ L.map ( \ l -> do let p = prefix l string p return $ do u <- liftIO $ ls2bs 7 "Usage: "# let un = u `hAppend` name l maybe ( priv_msg h cmds $ un `hAppend` p ) ( \ is -> do input <- liftIO $ ls2bs 7 " INPUT "# open <- liftIO $ ls2bs 2 "[ "# priv_msg h cmds $ un `hAppend` p `hAppend` ' ' `hAppend` open `hAppend` is `hAppend` input `hAppend` ']' ) $ input_seperator l ) ls