-- | A default help command implementation
module Calamity.Commands.Help (
  helpCommand',
  helpCommand,
) where

import Calamity.Client.Types (BotC)
import Calamity.Commands.Types
import Calamity.Types.Tellable
import qualified CalamityCommands.Help as CC
import Control.Monad (void)
import qualified Polysemy as P

{- | Given a 'CommandHandler', optionally a parent 'Group', and a list of 'Check's,
 construct a help command that will provide help for all the commands and
 groups in the passed 'CommandHandler'.
-}
helpCommand' :: (Tellable c, BotC r, CommandContext c) => CommandHandler c -> Maybe (Group c) -> [Check c] -> P.Sem r (Command c)
helpCommand' :: CommandHandler c
-> Maybe (Group c) -> [Check c] -> Sem r (Command c)
helpCommand' CommandHandler c
handler Maybe (Group c)
parent [Check c]
checks = CommandHandler c
-> Maybe (Group c)
-> [Check c]
-> (c -> Text -> Sem (Fail : r) ())
-> Sem r (Command c)
forall (m :: * -> *) (r :: EffectRow) c a.
(Monad m, Member (Final m) r, CommandContext m c a) =>
CommandHandler m c a
-> Maybe (Group m c a)
-> [Check m c]
-> (c -> Text -> Sem (Fail : r) a)
-> Sem r (Command m c a)
CC.helpCommand' CommandHandler c
handler Maybe (Group c)
parent [Check c]
checks (\c
a Text
b -> Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ())
-> Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ()
forall a b. (a -> b) -> a -> b
$ c -> Text -> Sem (Fail : r) (Either RestError Message)
forall msg (r :: EffectRow) t.
(BotC r, ToMessage msg, Tellable t) =>
t -> msg -> Sem r (Either RestError Message)
tell c
a Text
b)

{- | Create and register the default help command for all the commands registered
 in the commands DSL this is used in. The @render@ parameter is used so you can
 determine how the help should be rendered, for example it could be
 @'putStrLn'@, or a pure function such as @'pure' . 'Left'@

 The registered command will have the name \'help\', called with no parameters
 it will render help for the top-level groups and commands, for example:

 @
 The following groups exist:
 - reanimate
 - prefix[prefixes]
 - alias[aliases]
 - remind[reminder|reminders]

 The following commands exist:
 - help :[Text]
 @

 Both commands and groups are listed in the form: @\<name\>[\<alias 0\>|\<alias 1\>]@,
 commands also have their parameter list shown.

 If a path to a group is passed, the help, aliases, and pre-invokation checks
 will be listed, along with the subgroups and commands, For example:

 @
 Help for group remind:
 Group: remind
 Aliases: reminder reminders
 Commands related to making reminders

 The following child commands exist:
 - list
 - remove reminder_id:Text
 - add :KleenePlusConcat Text
 @

 If a command path is passed, the usage, checks and help for the command are
 shown, for example:

 @
 Help for command add:
 Usage: c!prefix add prefix:Text
 Checks: prefixLimit guildOnly

 Add a new prefix
 @
-}
helpCommand :: (Tellable c, BotC r, CommandContext c) => P.Sem (DSLState c r) (Command c)
helpCommand :: Sem (DSLState c r) (Command c)
helpCommand = (c -> Text -> Sem (Fail : r) ()) -> Sem (DSLState c r) (Command c)
forall c (m :: * -> *) a (r :: EffectRow).
(Monad m, Member (Final m) r, CommandContext m c a) =>
(c -> Text -> Sem (Fail : r) a)
-> Sem (DSLState m c a r) (Command m c a)
CC.helpCommand (\c
a Text
b -> Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ())
-> Sem (Fail : r) (Either RestError Message) -> Sem (Fail : r) ()
forall a b. (a -> b) -> a -> b
$ c -> Text -> Sem (Fail : r) (Either RestError Message)
forall msg (r :: EffectRow) t.
(BotC r, ToMessage msg, Tellable t) =>
t -> msg -> Sem r (Either RestError Message)
tell c
a Text
b)