Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main module of the butcher interface. It reexports everything that is exposed in the submodules.
- data Input
- = InputString String
- | InputArgs [String]
- type CmdParser f out = Free (CmdParserF f out)
- data ParsingError = ParsingError {
- _pe_messages :: [String]
- _pe_remaining :: Input
- data CommandDesc out
- cmd_out :: forall out. Lens' (CommandDesc out) (Maybe out)
- runCmdParserSimple :: String -> CmdParser Identity out () -> Either String out
- runCmdParser :: Maybe String -> Input -> CmdParser Identity out () -> (CommandDesc (), Either ParsingError (CommandDesc out))
- runCmdParserExt :: Maybe String -> Input -> CmdParser Identity out () -> (CommandDesc (), Input, Either ParsingError (CommandDesc out))
- runCmdParserA :: forall f out. Applicative f => Maybe String -> Input -> CmdParser f out () -> f (CommandDesc (), Either ParsingError (CommandDesc out))
- runCmdParserAExt :: forall f out. Applicative f => Maybe String -> Input -> CmdParser f out () -> f (CommandDesc (), Input, Either ParsingError (CommandDesc out))
- runCmdParserWithHelpDesc :: Maybe String -> Input -> (CommandDesc () -> CmdParser Identity out ()) -> (CommandDesc (), Either ParsingError (CommandDesc out))
- checkCmdParser :: forall f out. Maybe String -> CmdParser f out () -> Either String (CommandDesc ())
- module UI.Butcher.Monadic.Command
- module UI.Butcher.Monadic.Pretty
- module UI.Butcher.Monadic.IO
- addHelpCommand :: Applicative f => CommandDesc () -> CmdParser f (IO ()) ()
- addButcherDebugCommand :: Applicative f => CmdParser f (IO ()) ()
- mapOut :: (outa -> outb) -> CmdParser f outa () -> CmdParser f outb ()
Types
Butcher supports two input modi: String
and [String]
. Program
arguments have the latter form, while parsing interactive command input
(e.g. when you implement a terminal of sorts) is easier when you can
process the full String
without having to wordify it first by some
means (and List.words is not the right approach in many situations.)
data ParsingError Source #
Information about an error that occured when trying to parse some Input
using some CmdParser
.
ParsingError | |
|
data CommandDesc out Source #
A representation/description of a command parser built via the
CmdParser
monad. Can be transformed into a pretty Doc to display
as usage/help via ppUsage
and related functions.
Note that there is the _cmd_out
accessor that contains Maybe out
which
might be useful after successful parsing.
Functor CommandDesc Source # | |
Show (CommandDesc out) Source # | |
Run or Check CmdParsers
runCmdParserSimple :: String -> CmdParser Identity out () -> Either String out Source #
Wrapper around runCmdParser
for very simple usage: Accept a String
input and return only the output from the parser, returning Nothing
in
any error case.
:: Maybe String | program name to be used for the top-level |
-> Input | input to be processed |
-> CmdParser Identity out () | parser to use |
-> (CommandDesc (), Either ParsingError (CommandDesc out)) |
Run a CmdParser
on the given input, returning:
a) A CommandDesc ()
that accurately represents the subcommand that was
reached, even if parsing failed. Because this is returned always, the
argument is ()
because "out" requires a successful parse.
b) Either an error or the result of a successful parse, including a proper "CommandDesc out" from which an "out" can be extracted (presuming that the command has an implementation).
:: Maybe String | program name to be used for the top-level |
-> Input | input to be processed |
-> CmdParser Identity out () | parser to use |
-> (CommandDesc (), Input, Either ParsingError (CommandDesc out)) |
Like runCmdParser
, but also returning all input after the last
successfully parsed subcommand. E.g. for some input
"myprog foo bar -v --wrong" where parsing fails at "--wrong", this will
contain the full "-v --wrong". Useful for interactive feedback stuff.
:: Applicative f | |
=> Maybe String | program name to be used for the top-level |
-> Input | input to be processed |
-> CmdParser f out () | parser to use |
-> f (CommandDesc (), Either ParsingError (CommandDesc out)) |
The Applicative-enabled version of runCmdParser
.
:: Applicative f | |
=> Maybe String | program name to be used for the top-level |
-> Input | input to be processed |
-> CmdParser f out () | parser to use |
-> f (CommandDesc (), Input, Either ParsingError (CommandDesc out)) |
The Applicative-enabled version of runCmdParserExt
.
runCmdParserWithHelpDesc Source #
:: Maybe String | program name to be used for the top-level |
-> Input | input to be processed |
-> (CommandDesc () -> CmdParser Identity out ()) | parser to use |
-> (CommandDesc (), Either ParsingError (CommandDesc out)) |
Like runCmdParser
, but with one additional twist: You get access
to a knot-tied complete CommandDesc for this full command. Useful in
combination with addHelpCommand
.
Note that the CommandDesc ()
in the output is _not_ the same value as the
parameter passed to the parser function: The output value contains a more
"shallow" description. This is more efficient for complex CmdParsers when
used interactively, because non-relevant parts of the CmdParser are not
traversed unless the parser function argument is forced.
:: Maybe String | top-level command name |
-> CmdParser f out () | parser to check |
-> Either String (CommandDesc ()) |
Because butcher is evil (i.e. has constraints not encoded in the types;
see the README), this method can be used as a rough check that you did not
mess up. It traverses all possible parts of the CmdParser
thereby
ensuring that the CmdParser
has a valid structure.
This method also yields a _complete_ CommandDesc
output, where the other
runCmdParser* functions all traverse only a shallow structure around the
parts of the CmdParser
touched while parsing the current input.
Building CmdParsers
module UI.Butcher.Monadic.Command
PrettyPrinting CommandDescs (usage/help)
module UI.Butcher.Monadic.Pretty
Wrapper around System.Environment.getArgs
module UI.Butcher.Monadic.IO
Builtin commands
addHelpCommand :: Applicative f => CommandDesc () -> CmdParser f (IO ()) () Source #
Adds a proper full help command. To obtain the CommandDesc
value, see
cmdRunParserWithHelpDesc
or
mainFromCmdParserWithHelpDesc
.
addButcherDebugCommand :: Applicative f => CmdParser f (IO ()) () Source #
Prints the raw CommandDesc structure.