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

CalamityCommands.Utils

Description

Command handler utilities

Synopsis

Documentation

buildCommands :: forall r c m a x. (Monad m, MonadFix m, Member (Final m) r) => Sem (DSLState m c a r) x -> Sem r (CommandHandler m c a, x) Source #

Run a command DSL, returning the constructed CommandHandler

processCommands Source #

Arguments

:: (Monad m, Members '[ParsePrefix msg, ConstructContext msg c m a, Embed m] r, CommandContext m c a) 
=> CommandHandler m c a 
-> msg

The message that invoked the command

-> Sem r (Maybe (Either (CmdInvokeFailReason c) (c, a))) 

Manages parsing messages and handling commands for a CommandHandler.

Returns Nothing if the prefix didn't match.

Returns Right with the context and result if the command succeeded in parsing and running, Left with the reason otherwise.

handleCommands Source #

Arguments

:: (Monad m, Members '[ConstructContext msg c m a, Embed m] r, CommandContext m c a) 
=> CommandHandler m c a 
-> msg

The message that invoked the command

-> Text

The prefix used

-> Text

The command string, without a prefix

-> Sem r (Either (CmdInvokeFailReason c) (c, a)) 

Manages finding the invoked command and parsing parameters for a CommandHandler.

Returns Right with the context and result if the command succeeded in parsing and running, Left with the reason otherwise.

findCommand :: forall c a m. CommandHandler m c a -> Text -> Either [Text] (Command m c a, Text) Source #

Attempt to find what command was used.

On error: returns the path of existing groups that were found, so "group0 group1 group2 notacommand" will error with Left ["group0", "group1", "group2"]

On success: returns the command that was invoked, and the remaining text after it.

This function isn't greedy, if you have a group and a command at the same level, this will find the command first and ignore the group.

data CmdInvokeFailReason c Source #

Instances

Instances details
Show c => Show (CmdInvokeFailReason c) Source # 
Instance details

Defined in CalamityCommands.Utils

Generic (CmdInvokeFailReason c) Source # 
Instance details

Defined in CalamityCommands.Utils

Associated Types

type Rep (CmdInvokeFailReason c) :: Type -> Type #

type Rep (CmdInvokeFailReason c) Source # 
Instance details

Defined in CalamityCommands.Utils

type Rep (CmdInvokeFailReason c) = D1 ('MetaData "CmdInvokeFailReason" "CalamityCommands.Utils" "calamity-commands-0.1.3.0-inplace" 'False) (C1 ('MetaCons "NoContext" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text])) :+: C1 ('MetaCons "CommandInvokeError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommandError))))