Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
CalamityCommands commands This module exports the DSL and core types for using commands
Synopsis
- module CalamityCommands.Context
- module CalamityCommands.Dsl
- module CalamityCommands.Error
- module CalamityCommands.Handler
- module CalamityCommands.Utils
- module CalamityCommands.ParsePrefix
- module CalamityCommands.Help
- data Named (s :: Symbol) (a :: Type)
- data KleenePlusConcat (a :: Type)
- data KleeneStarConcat (a :: Type)
- class Typeable a => ParameterParser (a :: Type) c r where
- type ParserResult a
- parameterInfo :: ParameterInfo
- parameterDescription :: Text
- parse :: Sem (ParserEffs c r) (ParserResult a)
Documentation
module CalamityCommands.Context
module CalamityCommands.Dsl
module CalamityCommands.Error
module CalamityCommands.Handler
module CalamityCommands.Utils
module CalamityCommands.ParsePrefix
module CalamityCommands.Help
Parameter parsers
data Named (s :: Symbol) (a :: Type) Source #
A named parameter, used to attach the name s
to a type in the command's
help output
Instances
(KnownSymbol s, ParameterParser a c r) => ParameterParser (Named s a) c r Source # | |
Defined in CalamityCommands.Parser type ParserResult (Named s a) Source # parameterInfo :: ParameterInfo Source # parameterDescription :: Text Source # parse :: Sem (ParserEffs c r) (ParserResult (Named s a)) Source # | |
type ParserResult (Named s a) Source # | |
Defined in CalamityCommands.Parser |
data KleenePlusConcat (a :: Type) Source #
A parser that consumes one or more of a
then concatenates them together.
therefore consumes all remaining input.KleenePlusConcat
Text
Instances
data KleeneStarConcat (a :: Type) Source #
A parser that consumes zero or more of a
then concatenates them together.
therefore consumes all remaining input.KleeneStarConcat
Text
Instances
class Typeable a => ParameterParser (a :: Type) c r where Source #
A typeclass for things that can be parsed as parameters to commands.
Any type that is an instance of ParamerParser can be used in the type level
parameter ps
of command
,
buildCommand
, etc.
type ParserResult a Source #
type ParserResult a = a
parameterInfo :: ParameterInfo Source #
default parameterInfo :: ParameterInfo Source #
parameterDescription :: Text Source #
parse :: Sem (ParserEffs c r) (ParserResult a) Source #
Instances
Commands
This module provides abstractions for writing declarative commands, that support grouping, pre-invokation checks, and automatic argument parsing by using a type level list of parameter types.
A DSL is provided in CalamityCommands.Dsl for constructing commands declaratively.
You can implement ParameterParser
for your own types to allow them to be used in the
parameter list of commands.
A default help command is provided in CalamityCommands.Help which can be
added just by using helpCommand
inside the command declaration DSL.
Commands are parameterised over three types:
m
, the base monad of the command processor. This is used because all commands and checks run in their base monad in the current implementation, as a result, all commands will run with the monadic state remaining the same as when they were created. In the future this design decision may be revised to remove this constraint. For pure commands this may beIdentity
and for IO commands this may beIO
.c
, the context that is provided to each command invokation. The default context:BasicContext
stores the prefix, command, and unparsed parameters to the command. The context in use is decided by the interpreter forConstructContext
.a
, the result of a command invokation, for commands performing IO actions this is usually just()
.
Examples
Make a command handler, we don't actually use the context and therefore this handler is generic over the context used:
h' ::CommandContext
Identity
c (Either
Text
Int
) =>CommandHandler
Identity
c (Either
Text
Int
) h' =runIdentity
.runFinal
$ do (h, _) <-buildCommands
$ docommand
@'[Int, Int] "add" $ ctx a b ->pure
$Right
(a+
b)command
@'[Int, Int] "mul" $ ctx a b ->pure
$Right
(a*
b)helpCommand
(pure
.Left
) pure h
To use the commands we need to provide the interpreters for
ConstructContext
and ParsePrefix
, the default provided ones are being
used here: useBasicContext
which makes ctx ~
, and
BasicContext
which treats any input starting with useConstantPrefix
"!"!
as a
command.
The processCommands
function can then be used to parse and invoke commands,
since commands are generic over the monad they run in we use
to have the commands interpreted purely.runIdentity
. runFinal
.
embedToFinal
This function r
takes an input string such as "!add 1 2", and then looks up
the invoked command and runs it, returning the result.
r ::Text
->Maybe
(Either
(CmdInvokeFailReason
(BasicContext
Identity
(Either
Text
Int
))) (BasicContext
Identity
(Either
Text
Int
),Either
Text
Int
)) r =runIdentity
.runFinal
.embedToFinal
.useBasicContext
.useConstantPrefix
"!" .processCommands
h'
Then to display the result of processing the command nicely, we can use a something like this function, which prints the result of a command if one was invoked successfully, and prints the error nicely if not.
rm ::Text
-> IO () rm s = case r s of Just (Right (_, Right r)) -> print r Just (Right (_, Left h)) ->putStrLn
h Just (Left (CommandInvokeError
_ (ParseError
t r))) ->putStrLn
("Parsing parameter "<>
t<>
" failed with reason: "<>
r) _ -> pure ()
>>>
rm "!add 1 1"
2
>>>
rm "!add blah 1"
Parsing parameter :Int failed with reason: 1:2: | 1 | blah 1 | ^ unexpected 'b' expecting '+', '-', integer, or white space
>>>
rm "!help"
``` The following commands exist: - mul :Int, :Int - help :[Text] - add :Int, :Int ```
>>>
rm "!help add"
Help for command `add`: ``` Usage: !add :Int, :Int This command or group has no help. ```