calamity-0.1.19.2: A library for writing discord bots in haskell
Safe HaskellNone
LanguageHaskell2010

Calamity.Commands.Dsl

Description

A DSL for generating commands and groups

Synopsis

Documentation

command Source #

Arguments

:: forall ps r. (Member (Final IO) r, TypedCommandC ps r) 
=> Text

The name of the command

-> (Context -> CommandForParsers ps r)

The callback for this command

-> Sem (DSLState r) Command 

Given the name of a command and a callback, and a type level list of the parameters, build and register a command.

The parent group, visibility, checks, and command help are drawn from the reader context.

Examples

Building a command that bans a user by id.

command @'[Named "user" (Snowflake User),
               Named "reason" (KleeneStarConcat Text)]
   "ban" $ ctx uid r -> case (ctx ^. #guild) of
     Just guild -> do
       void . invoke . reason r $ CreateGuildBan guild uid
       void $ tell ctx ("Banned user `" <> showt uid <> "` with reason: " <> r)
     Nothing -> void $ tell @Text ctx "Can only ban users from guilds."

command' Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the command

-> [Text]

The names of the command's parameters

-> (Context -> Sem r (Either CommandError a))

The parser for this command

-> ((Context, a) -> Sem (Fail ': r) ())

The callback for this command

-> Sem (DSLState r) Command 

Given the command name and parameter names, parser and callback for a command in the Sem monad, build a command by transforming the Polysemy actions into IO actions. Then register the command.

The parent group, visibility, checks, and command help are drawn from the reader context.

commandA Source #

Arguments

:: forall ps r. (Member (Final IO) r, TypedCommandC ps r) 
=> Text

The name of the command

-> [Text]

The aliases for the command

-> (Context -> CommandForParsers ps r)

The callback for this command

-> Sem (DSLState r) Command 

Given the name and aliases of a command and a callback, and a type level list of the parameters, build and register a command.

The parent group, visibility, checks, and command help are drawn from the reader context.

Examples

Building a command that bans a user by id.

commandA @'[Named "user" (Snowflake User),
               Named "reason" (KleeneStarConcat Text)]
   "ban" [] $ ctx uid r -> case (ctx ^. #guild) of
     Just guild -> do
       void . invoke . reason r $ CreateGuildBan guild uid
       void $ tell ctx ("Banned user `" <> showt uid <> "` with reason: " <> r)
     Nothing -> void $ tell @Text ctx "Can only ban users from guilds."

commandA' Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the command

-> [Text]

The aliases for the command

-> [Text]

The names of the command's parameters

-> (Context -> Sem r (Either CommandError a))

The parser for this command

-> ((Context, a) -> Sem (Fail ': r) ())

The callback for this command

-> Sem (DSLState r) Command 

Given the command name, aliases, and parameter names, parser and callback for a command in the Sem monad, build a command by transforming the Polysemy actions into IO actions. Then register the command.

The parent group, visibility, checks, and command help are drawn from the reader context.

hide :: Member (Tagged "hidden" (Reader Bool)) r => Sem r a -> Sem r a Source #

Set the visibility of any groups or commands registered inside the given action to hidden.

help :: Member (Reader (Context -> Text)) r => (Context -> Text) -> Sem r a -> Sem r a Source #

Set the help for any groups or commands registered inside the given action.

requires :: [Check] -> Sem (DSLState r) a -> Sem (DSLState r) a Source #

Add to the list of checks for any commands registered inside the given action.

requires' Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the check

-> (Context -> Sem r (Maybe Text))

The callback for the check

-> Sem (DSLState r) a 
-> Sem (DSLState r) a 

Construct a check and add it to the list of checks for any commands registered inside the given action.

Refer to Check for more info on checks.

requiresPure :: [(Text, Context -> Maybe Text)] -> Sem (DSLState r) a -> Sem (DSLState r) a Source #

Construct some pure checks and add them to the list of checks for any commands registered inside the given action.

Refer to Check for more info on checks.

group Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the group

-> Sem (DSLState r) a 
-> Sem (DSLState r) a 

Construct a group and place any commands registered in the given action into the new group.

This also resets the help function back to it's original value, use group' if you don't want that (i.e. your help function is context aware).

group' :: Member (Final IO) r => Text -> Sem (DSLState r) a -> Sem (DSLState r) a Source #

Construct a group and place any commands registered in the given action into the new group.

The parent group, visibility, checks, and command help are drawn from the reader context.

Unlike help this doesn't reset the help function back to it's original value.

groupA Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the group

-> [Text]

The aliases of the group

-> Sem (DSLState r) a 
-> Sem (DSLState r) a 

Construct a group with aliases and place any commands registered in the given action into the new group.

The parent group, visibility, checks, and command help are drawn from the reader context.

This also resets the help function back to it's original value, use group' if you don't want that (i.e. your help function is context aware).

groupA' Source #

Arguments

:: Member (Final IO) r 
=> Text

The name of the group

-> [Text]

The aliases of the group

-> Sem (DSLState r) a 
-> Sem (DSLState r) a 

Construct a group with aliases and place any commands registered in the given action into the new group.

The parent group, visibility, checks, and command help are drawn from the reader context.

Unlike help this doesn't reset the help function back to it's original value.

type DSLState r = LocalWriter (HashMap Text (Command, AliasType)) ': (LocalWriter (HashMap Text (Group, AliasType)) ': (Reader (Maybe Group) ': (Tagged "hidden" (Reader Bool) ': (Reader (Context -> Text) ': (Tagged "original-help" (Reader (Context -> Text)) ': (Reader [Check] ': (Reader CommandHandler ': (Fixpoint ': r)))))))) Source #

raiseDSL :: Sem r a -> Sem (DSLState r) a Source #

fetchHandler :: Sem (DSLState r) CommandHandler Source #

Retrieve the final command handler for this block