module Lambdabot.Plugin.Core.Help (helpPlugin) where
import Lambdabot.Command
import Lambdabot.Message (Message)
import Lambdabot.Module
import Lambdabot.Monad
import Lambdabot.Plugin
import Lambdabot.Util
import Control.Monad.Reader
helpPlugin :: Module ()
helpPlugin :: Module ()
helpPlugin = Module ()
forall st. Module st
newModule
{ moduleCmds :: ModuleT () LB [Command (ModuleT () LB)]
moduleCmds = [Command (ModuleT () LB)]
-> ModuleT () LB [Command (ModuleT () LB)]
forall (m :: * -> *) a. Monad m => a -> m a
return
[ (String -> Command Identity
command String
"help")
{ help :: Cmd (ModuleT () LB) ()
help = String -> Cmd (ModuleT () LB) ()
forall (m :: * -> *). Monad m => String -> Cmd m ()
say String
"help <command>. Ask for help for <command>. Try 'list' for all commands"
, process :: String -> Cmd (ModuleT () LB) ()
process = \String
args -> (forall a. Message a => a -> Cmd (ModuleT () LB) ())
-> Cmd (ModuleT () LB) ()
forall (m :: * -> *) t.
Monad m =>
(forall a. Message a => a -> Cmd m t) -> Cmd m t
withMsg ((forall a. Message a => a -> Cmd (ModuleT () LB) ())
-> Cmd (ModuleT () LB) ())
-> (forall a. Message a => a -> Cmd (ModuleT () LB) ())
-> Cmd (ModuleT () LB) ()
forall a b. (a -> b) -> a -> b
$ \a
msg -> do
Nick
tgt <- Cmd (ModuleT () LB) Nick
forall (m :: * -> *). Monad m => Cmd m Nick
getTarget
LB [String] -> Cmd (ModuleT () LB) [String]
forall (m :: * -> *) a. MonadLB m => LB a -> m a
lb (a -> Nick -> String -> LB [String]
forall t. Message t => t -> Nick -> String -> LB [String]
doHelp a
msg Nick
tgt String
args) Cmd (ModuleT () LB) [String]
-> ([String] -> Cmd (ModuleT () LB) ()) -> Cmd (ModuleT () LB) ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> Cmd (ModuleT () LB) ())
-> [String] -> Cmd (ModuleT () LB) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> Cmd (ModuleT () LB) ()
forall (m :: * -> *). Monad m => String -> Cmd m ()
say
}
]
}
moduleHelp :: (Monad m, Message a) =>
Command m -> a -> Nick -> String -> m [String]
moduleHelp :: Command m -> a -> Nick -> String -> m [String]
moduleHelp Command m
theCmd a
msg Nick
tgt String
cmd =
Cmd m () -> a -> Nick -> String -> m [String]
forall (m :: * -> *) a t.
(Monad m, Message a) =>
Cmd m t -> a -> Nick -> String -> m [String]
execCmd (Command m -> Cmd m ()
forall (m :: * -> *). Command m -> Cmd m ()
help Command m
theCmd) a
msg Nick
tgt String
cmd
doHelp :: Message t => t -> Nick -> [Char] -> LB [[Char]]
doHelp :: t -> Nick -> String -> LB [String]
doHelp t
msg Nick
tgt [] = t -> Nick -> String -> LB [String]
forall t. Message t => t -> Nick -> String -> LB [String]
doHelp t
msg Nick
tgt String
"help"
doHelp t
msg Nick
tgt String
rest =
String
-> LB [String]
-> (forall st. Command (ModuleT st LB) -> ModuleT st LB [String])
-> LB [String]
forall a.
String
-> LB a
-> (forall st. Command (ModuleT st LB) -> ModuleT st LB a)
-> LB a
withCommand String
arg
(String
-> LB [String]
-> (forall st. ModuleT st LB [String])
-> LB [String]
forall a. String -> LB a -> (forall st. ModuleT st LB a) -> LB a
inModuleNamed String
arg
(t -> Nick -> String -> LB [String]
forall t. Message t => t -> Nick -> String -> LB [String]
doHelp t
msg Nick
tgt String
"help")
(do
[Command (ModuleT st LB)]
cmds <- Module st -> ModuleT st LB [Command (ModuleT st LB)]
forall st. Module st -> ModuleT st LB [Command (ModuleT st LB)]
moduleCmds (Module st -> ModuleT st LB [Command (ModuleT st LB)])
-> ModuleT st LB (Module st)
-> ModuleT st LB [Command (ModuleT st LB)]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ModuleInfo st -> Module st) -> ModuleT st LB (Module st)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ModuleInfo st -> Module st
forall st. ModuleInfo st -> Module st
theModule
let ss :: [String]
ss = [Command (ModuleT st LB)]
cmds [Command (ModuleT st LB)]
-> (Command (ModuleT st LB) -> [String]) -> [String]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Command (ModuleT st LB) -> [String]
forall (m :: * -> *). Command m -> [String]
cmdNames
let s :: String
s | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
ss = String
arg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is a module."
| Bool
otherwise = String
arg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" provides: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => [a] -> String
showClean [String]
ss
[String] -> ModuleT st LB [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String
s]))
(\Command (ModuleT st LB)
theCmd -> Command (ModuleT st LB)
-> t -> Nick -> String -> ModuleT st LB [String]
forall (m :: * -> *) a.
(Monad m, Message a) =>
Command m -> a -> Nick -> String -> m [String]
moduleHelp Command (ModuleT st LB)
theCmd t
msg Nick
tgt String
arg)
where (String
arg:[String]
_) = String -> [String]
words String
rest