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

CalamityCommands.Context

Description

Command context typeclass

Synopsis

Documentation

class CommandContext m c a | c -> m, c -> a where Source #

Methods

ctxPrefix :: c -> Text Source #

The prefix that was used to invoke the command

ctxCommand :: c -> Command m c a Source #

The command that was invoked

ctxUnparsedParams :: c -> Text Source #

The message remaining after consuming the prefix

Instances

Instances details
CommandContext m (BasicContext m a) a Source # 
Instance details

Defined in CalamityCommands.Context

data ConstructContext msg ctx m' a' m a where Source #

An effect for constructing the context for a command

Constructors

ConstructContext

Construct a context for a command invokation, returning Just context on success, or Nothing if a context could not be constructed

Fields

Instances

Instances details
type DefiningModule (ConstructContext :: Type -> Type -> (Type -> Type) -> Type -> k -> Type -> Type) Source # 
Instance details

Defined in CalamityCommands.Context

type DefiningModule (ConstructContext :: Type -> Type -> (Type -> Type) -> Type -> k -> Type -> Type) = "CalamityCommands.Context"

constructContext :: forall msg ctx m' a' r. MemberWithError (ConstructContext msg ctx m' a') r => (Text, Command m' ctx a', Text) -> msg -> Sem r (Maybe ctx) Source #

data BasicContext m a Source #

A basic context that only knows the prefix used and the unparsed input

Constructors

BasicContext 

Instances

Instances details
CommandContext m (BasicContext m a) a Source # 
Instance details

Defined in CalamityCommands.Context

Show (BasicContext m a) Source # 
Instance details

Defined in CalamityCommands.Context

Generic (BasicContext m a) Source # 
Instance details

Defined in CalamityCommands.Context

Associated Types

type Rep (BasicContext m a) :: Type -> Type #

Methods

from :: BasicContext m a -> Rep (BasicContext m a) x #

to :: Rep (BasicContext m a) x -> BasicContext m a #

type Rep (BasicContext m a) Source # 
Instance details

Defined in CalamityCommands.Context

type Rep (BasicContext m a) = D1 ('MetaData "BasicContext" "CalamityCommands.Context" "calamity-commands-0.1.3.0-inplace" 'False) (C1 ('MetaCons "BasicContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "bcPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "bcCommand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Command m (BasicContext m a) a)) :*: S1 ('MetaSel ('Just "bcUnparsedParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

useBasicContext :: Sem (ConstructContext msg (BasicContext m a') m a' ': r) a -> Sem r a Source #

A default interpretation for ConstructContext that constructs a BasicContext