butcher-1.3.3.1: Chops a command or program invocation into digestable pieces.

Safe HaskellNone
LanguageHaskell2010

UI.Butcher.Monadic

Contents

Description

Reexports of everything that is exposed in the submodules.

Synopsis

Types

data Input Source #

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.)

Instances
Eq Input Source # 
Instance details

Defined in UI.Butcher.Monadic.Internal.Types

Methods

(==) :: Input -> Input -> Bool #

(/=) :: Input -> Input -> Bool #

Show Input Source # 
Instance details

Defined in UI.Butcher.Monadic.Internal.Types

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

type CmdParser f out = Free (CmdParserF f out) Source #

The CmdParser monad type. It is a free monad over some functor but users of butcher don't need to know more than that CmdParser is a Monad.

data ParsingError Source #

Information about an error that occured when trying to parse some Input using some CmdParser.

Constructors

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.

Instances
Functor CommandDesc Source # 
Instance details

Defined in UI.Butcher.Monadic.Internal.Types

Methods

fmap :: (a -> b) -> CommandDesc a -> CommandDesc b #

(<$) :: a -> CommandDesc b -> CommandDesc a #

Show (CommandDesc out) Source # 
Instance details

Defined in UI.Butcher.Monadic.Internal.Types

Methods

showsPrec :: Int -> CommandDesc out -> ShowS #

show :: CommandDesc out -> String #

showList :: [CommandDesc out] -> ShowS #

cmd_out :: forall out. Lens' (CommandDesc out) (Maybe 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, or a plain error string on failure.

runCmdParser Source #

Arguments

:: Maybe String

program name to be used for the top-level CommandDesc

-> 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).

runCmdParserExt Source #

Arguments

:: Maybe String

program name to be used for the top-level CommandDesc

-> 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.

runCmdParserA Source #

Arguments

:: Applicative f 
=> Maybe String

program name to be used for the top-level CommandDesc

-> Input

input to be processed

-> CmdParser f out ()

parser to use

-> f (CommandDesc (), Either ParsingError (CommandDesc out)) 

The Applicative-enabled version of runCmdParser.

runCmdParserAExt Source #

Arguments

:: Applicative f 
=> Maybe String

program name to be used for the top-level CommandDesc

-> 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 #

Arguments

:: Maybe String

program name to be used for the top-level CommandDesc

-> 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.

checkCmdParser Source #

Arguments

:: 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

PrettyPrinting CommandDescs (usage/help)

Wrapper around System.Environment.getArgs

Utilities for interactive feedback of commandlines (completions etc.)

Builtin commands

addHelpCommand :: Applicative f => CommandDesc a -> CmdParser f (IO ()) () Source #

Adds a proper full help command. To obtain the CommandDesc value, see cmdRunParserWithHelpDesc or mainFromCmdParserWithHelpDesc.

addHelpCommand = addHelpCommandWith
  (pure . PP.renderStyle PP.style { PP.ribbonsPerLine = 1.0 } . ppHelpShallow)

addHelpCommand2 :: Applicative f => CommandDesc a -> CmdParser f (IO ()) () Source #

Adds a proper full help command. In contrast to addHelpCommand, this version is a bit more verbose about available subcommands as it includes their synopses.

To obtain the CommandDesc value, see cmdRunParserWithHelpDesc or mainFromCmdParserWithHelpDesc.

addHelpCommand2 = addHelpCommandWith
  (pure . PP.renderStyle PP.style { PP.ribbonsPerLine = 1.0 } . ppHelpDepthOne)

addHelpCommandWith :: Applicative f => (CommandDesc a -> IO String) -> CommandDesc a -> CmdParser f (IO ()) () Source #

Adds a proper full help command, using the specified function to turn the relevant subcommand's CommandDesc into a String.

addButcherDebugCommand :: Applicative f => CmdParser f (IO ()) () Source #

Prints the raw CommandDesc structure.

addShellCompletionCommand :: CmdParser Identity (IO ()) () -> CmdParser Identity (IO ()) () Source #

Adds the "completion" command and several subcommands.

This command can be used in the following manner:

$ source <(foo completion bash-script foo)

addShellCompletionCommand' :: (CommandDesc out -> CmdParser Identity (IO ()) ()) -> CmdParser Identity (IO ()) () Source #

Adds the "completion" command and several subcommands

This command can be used in the following manner:

$ source <(foo completion bash-script foo)

Advanced usage

mapOut :: (outa -> outb) -> CmdParser f outa a -> CmdParser f outb a Source #

map over the out type argument

emptyCommandDesc :: CommandDesc out Source #

Empty CommandDesc value. Mostly for butcher-internal usage.