calamity-0.1.18.1: 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 :: forall ps r. (Member (Final IO) r, TypedCommandC ps r) => Text -> (Context -> CommandForParsers ps r) -> Sem (DSLState r) Command Source #

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

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' :: Member (Final IO) r => Text -> [Text] -> (Context -> Sem r (Either CommandError a)) -> ((Context, a) -> Sem (Fail ': r) ()) -> Sem (DSLState r) Command Source #

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, checks, and command help are drawn from the reader context.

commandA Source #

Arguments

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

name

-> [Text]

aliases

-> (Context -> CommandForParsers ps r) 
-> 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.

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

name

-> [Text]

aliases

-> [Text]

parameter names

-> (Context -> Sem r (Either CommandError a)) 
-> ((Context, a) -> Sem (Fail ': r) ()) 
-> 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, checks, and command help are drawn from the reader context.

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' :: Member (Final IO) r => Text -> (Context -> Sem r (Maybe Text)) -> Sem (DSLState r) a -> Sem (DSLState r) a Source #

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

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.

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.

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' Source #

Arguments

:: Member (Final IO) r 
=> Text

name

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

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

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

groupA Source #

Arguments

:: Member (Final IO) r 
=> Text

name

-> [Text]

aliases

-> 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.

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

name

-> [Text]

aliases

-> 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.

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) ': (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