| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
CalamityCommands.CommandUtils
Description
Command utilities
Synopsis
- type TypedCommandC ps c a r = (ApplyTupRes (ParserResult (ListToTup ps)) (CommandSemType r a) ~ CommandForParsers ps r a, ParameterParser (ListToTup ps) c r, ApplyTup (ParserResult (ListToTup ps)) (CommandSemType r a), ParameterInfoForParsers ps c r)
- type family CommandForParsers (ps :: [Type]) r a where ...
- buildCommand :: forall ps c m a r. (Monad m, Member (Final m) r, TypedCommandC ps c a r, CommandContext m c a) => NonEmpty Text -> Maybe (Group m c a) -> Bool -> [Check m c] -> (c -> Text) -> (c -> CommandForParsers ps r a) -> Sem r (Command m c a)
- buildCommand' :: forall c m a p r. (Monad m, Member (Final m) r) => NonEmpty Text -> Maybe (Group m c a) -> Bool -> [Check m c] -> [ParameterInfo] -> (c -> Text) -> (c -> Sem r (Either CommandError p)) -> ((c, p) -> Sem (Fail ': r) a) -> Sem r (Command m c a)
- buildParser :: (Monad m, Member (Final m) r) => Text -> (c -> Sem r (Either CommandError a)) -> Sem r (c -> m (Either CommandError a))
- buildCallback :: (Monad m, Member (Final m) r) => ((c, p) -> Sem (Fail ': r) a) -> Sem r ((c, p) -> m (Either Text a))
- runCommand :: (Monad m, Member (Embed m) r) => c -> Command m c a -> Sem r (Either CommandError a)
- invokeCommand :: (Monad m, Member (Embed m) r) => c -> Command m c a -> Sem r (Either CommandError a)
- groupPath :: Group m c a -> [Text]
- commandPath :: Command m c a -> [Text]
- commandParams :: Command m c a -> Text
Documentation
type TypedCommandC ps c a r = (ApplyTupRes (ParserResult (ListToTup ps)) (CommandSemType r a) ~ CommandForParsers ps r a, ParameterParser (ListToTup ps) c r, ApplyTup (ParserResult (ListToTup ps)) (CommandSemType r a), ParameterInfoForParsers ps c r) Source #
Some constraints used for making parameter typed commands work
type family CommandForParsers (ps :: [Type]) r a where ... Source #
Transform a type level list of types implementing the ParameterParser typeclass into
the type a command callback matching those parameters should be.
As an example:
CommandForParsers[Text,Int,Named"something"Text] r a ~ (Text->Int->Text->Semr (Fail': r) a)
Equations
| CommandForParsers '[] r a = Sem (Fail ': r) a | |
| CommandForParsers (x ': xs) r a = ParserResult x -> CommandForParsers xs r a |
Arguments
| :: forall ps c m a r. (Monad m, Member (Final m) r, TypedCommandC ps c a r, CommandContext m c a) | |
| => NonEmpty Text | The name (and aliases) of the command |
| -> Maybe (Group m c a) | The parent group of the command |
| -> Bool | If the command is hidden |
| -> [Check m c] | The checks for the command |
| -> (c -> Text) | The help generator for this command |
| -> (c -> CommandForParsers ps r a) | The callback foor this command |
| -> Sem r (Command m c a) |
Given the properties of a Command, a callback, and a type level list of
the parameters, build a command by constructing a parser and wiring it up to
the callback.
Examples
Building a command that adds two numbers.
buildCommand@'[Named"a"Int,Named"b"Int] "add"Nothing[] (const"Add two integers") $ \ctx a b ->pure$Right(a+b)
Arguments
| :: forall c m a p r. (Monad m, Member (Final m) r) | |
| => NonEmpty Text | The name (and aliases) of the command |
| -> Maybe (Group m c a) | The parent group of the command |
| -> Bool | If the command is hidden |
| -> [Check m c] | The checks for the command |
| -> [ParameterInfo] | The command's parameter metadata |
| -> (c -> Text) | The help generator for this command |
| -> (c -> Sem r (Either CommandError p)) | The parser for this command |
| -> ((c, p) -> Sem (Fail ': r) a) | The callback for this command |
| -> Sem r (Command m c a) |
buildParser :: (Monad m, Member (Final m) r) => Text -> (c -> Sem r (Either CommandError a)) -> Sem r (c -> m (Either CommandError a)) Source #
Given the name of the command the parser is for and a parser function in
the Sem monad, build a parser by transforming the Polysemy action into an
m action.
buildCallback :: (Monad m, Member (Final m) r) => ((c, p) -> Sem (Fail ': r) a) -> Sem r ((c, p) -> m (Either Text a)) Source #
Given a callback for a command in the Sem monad, build a command callback by
transforming the Polysemy action into an m action.
runCommand :: (Monad m, Member (Embed m) r) => c -> Command m c a -> Sem r (Either CommandError a) Source #
Given an invokation Context c, run a command. This does not perform the command's checks.
invokeCommand :: (Monad m, Member (Embed m) r) => c -> Command m c a -> Sem r (Either CommandError a) Source #
Given an invokation Context c, first run all of the command's checks, then
run the command if they all pass.
commandPath :: Command m c a -> [Text] Source #
commandParams :: Command m c a -> Text Source #
Format a command's parameters