calamity-commands-0.2.0.0: A library for declaring, parsing, and invoking text-input based commands
Safe HaskellNone
LanguageHaskell2010

CalamityCommands.Dsl

Contents

Description

A DSL for generating commands and groups

Synopsis

Commands DSL

This module provides a way of constructing bot commands in a declarative way.

The main component of this is the command function, which takes a type-level list of command parameters, the name, and the callback and produces a command. There are also the alternatives command', commandA and commandA', for when you want to handle parsing of the input yourself, and/or want aliases of the command.

The functions: hide, help, requires, and group can be used to change attributes of any commands declared inside the monadic action passed to them, for example:

hide $ do
  command @'[] "test" \ctx -> pure ()

In the above block, any command declared inside hide will have its 'hidden' flag set and will not be shown by the default help command: helpCommand

The helpCommand function can be used to create a help command for the commands DSL action it is used in, read its doc page for more information on how it functions.

The buildCommands function is used to construct a CommandHandler which can then be used with processCommands or handleCommands to process a command.

command Source #

Arguments

:: forall ps c a m r. (Monad m, Member (Final m) r, TypedCommandC ps c a r, CommandContext m c a) 
=> Text

The name of the command

-> (c -> CommandForParsers ps r a)

The callback for this command

-> Sem (DSLState m c a r) (Command m c a) 

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.

Command parameters are parsed by first invoking parse for the first Parser, then running the next parser on the remaining input, and so on.

Examples

Building a command that adds two numbers.

command @'[Named "a" Int, Named "b" Int]
  "add" $ \ctx a b -> pure $ Right (a + b)

command' Source #

Arguments

:: (Monad m, Member (Final m) r) 
=> Text

The name of the command

-> [ParameterInfo]

The command's parameter metadata

-> (c -> Sem r (Either CommandError p))

The parser for this command

-> ((c, p) -> Sem (Fail ': r) a)

The callback for this command

-> Sem (DSLState m c a r) (Command m c a) 

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 m actions. Then register the command.

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

commandA Source #

Arguments

:: forall ps c a m r. (Monad m, Member (Final m) r, TypedCommandC ps c a r, CommandContext m c a) 
=> Text

The name of the command

-> [Text]

The aliases for the command

-> (c -> CommandForParsers ps r a)

The callback for this command

-> Sem (DSLState m c a r) (Command m c a) 

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 adds two numbers.

commandA @'[Named "a" Int, Named "b" Int]
  "add" [] $ \ctx a b -> pure $ Right (a + b)

commandA' Source #

Arguments

:: forall p c a m r. (Monad m, Member (Final m) r) 
=> Text

The name of the command

-> [Text]

The aliases for the command

-> [ParameterInfo]

The command's parameter metadata

-> (c -> Sem r (Either CommandError p))

The parser for this command

-> ((c, p) -> Sem (Fail ': r) a)

The callback for this command

-> Sem (DSLState m c a r) (Command m c a) 

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 m 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 x -> Sem r x Source #

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

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

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

Examples

help (const "Add two integers") $
  command @'[Named "a" Int, Named "b" Int]
    "add" $ \ctx a b -> pure $ Right (a + b)

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

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

requires' Source #

Arguments

:: (Monad m, Member (Final m) r) 
=> Text

The name of the check

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

The callback for the check

-> Sem (DSLState m c a r) x 
-> Sem (DSLState m c a r) x 

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 :: Monad m => [(Text, c -> Maybe Text)] -> Sem (DSLState m c a r) x -> Sem (DSLState m c a r) x 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.

Examples

requiresPure [("always ok", const Nothing)] $
  command @'[Named "a" Int, Named "b" Int]
    "add" $ \ctx a b -> pure $ Right (a + b)

group Source #

Arguments

:: (Monad m, Member (Final m) r) 
=> Text

The name of the group

-> Sem (DSLState m c a r) x 
-> Sem (DSLState m c a r) x 

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

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

group' Source #

Arguments

:: Member (Final m) r 
=> Text

The name of the group

-> Sem (DSLState m c a r) x 
-> Sem (DSLState m c a r) x 

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 its original value.

groupA Source #

Arguments

:: forall x c m a r. (Monad m, Member (Final m) r) 
=> Text

The name of the group

-> [Text]

The aliases of the group

-> Sem (DSLState m c a r) x 
-> Sem (DSLState m c a r) x 

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 its original value, use group' if you don't want that (i.e. your help function is context aware).

groupA' Source #

Arguments

:: forall x c m a r. Member (Final m) r 
=> Text

The name of the group

-> [Text]

The aliases of the group

-> Sem (DSLState m c a r) x 
-> Sem (DSLState m c a r) x 

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 its original value.

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

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

fetchHandler :: Sem (DSLState m c a r) (CommandHandler m c a) Source #

Retrieve the final command handler for this block