Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides Commands for REPLs. Commands are there to provide high-level handling of user input and to offer functionality in a standard, composable way.
Whereas an Asker
is good for getting a single value, a Command
can get
multiple inputs and be composed with other commands.
Use cases:
- Getting specific numbers of arguments or optional arguments from the user. E.g.
{-# LANGUAGE OverloadedStrings #-} import Data.Text (unpack) asker :: Asker' IO String asker = Asker "Enter argument: " (Right . unpack) (return . Right) cmd = makeCommand3 "command" ("command"==) "description" True [asker,asker,asker] (t x y z -> putStrLn "yay!")
This is a command with 3 arguments. The user can enter the arguments in the same line or give them one by one:
>>>
command arg1 arg2 arg3
yay!
>>>
command
Enter argument:>>>
arg1
Enter argument:>>>
arg2
Enter argument:>>>
arg3
yay!
Had we set the bool above to False
, only the first form would have been allowed.
Arguments can contain whitespace if they are surrounded with quotes:
>>>
command "arg1 with spaces" arg2 arg3
yay!
Optional arguments are also possible:
cmd = makeCommandN "command" ("command"==) "description" True [asker] [optAsker] (t (x:xs) -> do putStrLn ("Required argument: " ++ x) if null xs then putStrLn "No optional argument." else putStrLn ("Optional argument: " ++ head xs))
>>>
command arg1
Required argument: arg1
>>>
command arg1 arg2
Required argument: arg1 Optional argument: arg2
- Creating command hierarchies, e.g.
commit = makeCommand 1 "commit" ... sendEmail = makeCommand "send-email" sendTweet = makeCommand "send-tweet" commit' = subcommand commit [sendEmail, sendTweet] main = makeREPLSimple [commit']
>>>
myVersionControl commit "my first commit" send-email
Here, commit
is the root command and sendEmail
, sendTweet
its two
possible sub-commands. The sub-commands get executed after their root command.
- Making a REPL out of some commands.
As above, one can use makeREPL
or makeREPLSimple
to create a
REPL out of a list of commands and use it as the main
function instead
of going through the chore of writing a loop it by hand.
- data Command m i a = Command {
- commandName :: Text
- commandTest :: i -> Bool
- commandDesc :: Text
- runPartialCommand :: [i] -> m (a, [i])
- oneOf :: Monoid i => Text -> Text -> [Command m i a] -> Command m i a
- subcommand :: (Monad m, Monoid i) => Command m i a -> [a -> Command m i b] -> Command m i b
- runCommand :: MonadThrow m => Command m Text a -> Text -> m a
- runSingleCommand :: MonadThrow m => Command m Text a -> Text -> m a
- runSingleCommandIf :: MonadThrow m => Command m Text a -> Text -> m (Maybe a)
- makeREPL :: (MonadIO m, MonadCatch m) => [Command m Text a] -> Command m Text b -> Command m Text c -> m Text -> [Handler m ()] -> m ()
- makeREPLSimple :: (MonadIO m, MonadCatch m) => [Command m Text a] -> m ()
- data SomeREPLError = forall e . Exception e => SomeREPLError e
- data SomeCommandError = forall e . Exception e => SomeCommandError e
- data MalformedParamsError = MalformedParamsError Text
- data TooFewParamsError = TooFewParamsError Int Int
- data TooManyParamsError = TooManyParamsError Int Int
- readArgs :: MonadThrow m => Text -> m [Text]
- getName :: Text -> Maybe Text
- defCommandTest :: [Text] -> Text -> Bool
- quoteArg :: Text -> Text
- summarizeCommands :: MonadIO m => [Command m2 i z] -> m ()
- makeCommand :: (MonadIO m, MonadCatch m, Monoid i) => Text -> (i -> Bool) -> Text -> (i -> m z) -> Command m i z
- makeCommand1 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> (Text -> a -> m z) -> Command m Text z
- makeCommand2 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> (Text -> a -> b -> m z) -> Command m Text z
- makeCommand3 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> (Text -> a -> b -> c -> m z) -> Command m Text z
- makeCommand4 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> Asker m d0 d -> (Text -> a -> b -> c -> d -> m z) -> Command m Text z
- makeCommand5 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> Asker m d0 d -> Asker m e0 e -> (Text -> a -> b -> c -> d -> e -> m z) -> Command m Text z
- makeCommand6 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> Asker m d0 d -> Asker m e0 e -> Asker m f0 f -> (Text -> a -> b -> c -> d -> e -> f -> m z) -> Command m Text z
- makeCommand7 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> Asker m d0 d -> Asker m e0 e -> Asker m f0 f -> Asker m g0 g -> (Text -> a -> b -> c -> d -> e -> f -> g -> m z) -> Command m Text z
- makeCommand8 :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> Asker m a0 a -> Asker m b0 b -> Asker m c0 c -> Asker m d0 d -> Asker m e0 e -> Asker m f0 f -> Asker m g0 g -> Asker m h0 h -> (Text -> a -> b -> c -> d -> e -> f -> g -> h -> m z) -> Command m Text z
- makeCommandN :: (MonadIO m, MonadCatch m) => Text -> (Text -> Bool) -> Text -> Bool -> [Asker m a0 a] -> [Asker m b0 a] -> (Text -> [a] -> m z) -> Command m Text z
- noOpCmd :: (MonadIO m, MonadCatch m) => Text -> [Text] -> Command m Text ()
- defExitCmd :: (MonadIO m, MonadCatch m) => Command m Text ()
- defHelpCmd :: (MonadIO m, MonadCatch m, Foldable f) => f (Command m0 a b) -> Command m Text ()
- defErrorHandler :: MonadIO m => [Handler m ()]
Command class
A REPL command, possibly with parameters.
Command | |
|
Takes a list xs
and executes the first command in a list whose
commandTest
matches the input.
Note that the resultant command c
s
runPartialCommand
should only be
executed with an input t
if 'commandTest c t' == True', where t'
is either
head (readArgs t)
or mempty
if t
is empty.
Otherwise, the result is undefined.
:: (Monad m, Monoid i) | |
=> Command m i a | The root command. |
-> [a -> Command m i b] | The subcommands that may follow it. This list must be finite. |
-> Command m i b |
Adds a list of possible subcommands after a command (that should leave some input unconsumed). Ignoring all the required parameters for a moment,
subcommand x xs = x >>- oneOf xs
Running commands
You can use runPartialCommand
to run a command as well, but one generally doesn't want left-over input.
runCommand :: MonadThrow m => Command m Text a -> Text -> m a Source
Runs the command with the input text as parameter, discarding any left-over input. The command test is disregarded.
Can throw:
runSingleCommand :: MonadThrow m => Command m Text a -> Text -> m a Source
Runs the command with the input text as parameter. The command test is disregarded.
Can throw:
MalformedParamsError
TooManyParamsError
, if any input is left unconsumed.
Note: TooManyParamsError
will only be thrown after the command's execution
is attempted. This is because of the subcommand mechanism, which prevents the
static determination of the number of required arguments.
runSingleCommandIf :: MonadThrow m => Command m Text a -> Text -> m (Maybe a) Source
Runs the command with the input text as parameter. If the input doesn't
pass the command test, Nothing
is returned.
Can throw:
MalformedParamsError
TooManyParamsError
, if any input is left unconsumed.
Making REPLs
:: (MonadIO m, MonadCatch m) | |
=> [Command m Text a] | The regular commands. |
-> Command m Text b | The "exit" command which terminates the loop. |
-> Command m Text c | The command that is called when none of the others match.
This one's |
-> m Text | The asker to execute before each command (i.e. the prompt). |
-> [Handler m ()] | List of Handlers for any exceptions that may arise.
The exception hierchy is rooted in |
-> m () | Asks the user repeatedly for input, until the input matches the command test of the "exit" command. |
Runs a REPL based on a set of commands. For a line of input, the commands are tried in following order:
- the "exit" command,
- all regular commands, and then
- the "unknown" command.
makeREPLSimple :: (MonadIO m, MonadCatch m) => [Command m Text a] -> m () Source
A variant of makeREPL
with some default settings:
- The "exit" command is
defExitCmd
. - The "unknown" command prints "Unknown command: input".
- The prompt is "> ".
- The error handler is
defErrorHandler
.
Exceptions
These are the exceptions that can be thrown during the course of command invocation (in addition to those that you throw yourself, of course).
SomeCommandError is an abstract exception and all others are its concrete subclasses. See the example in Control.Exception for details.
data SomeCommandError Source
Generic error related to command execution.
forall e . Exception e => SomeCommandError e |
data MalformedParamsError Source
The input of a command was malformed and could not interpreted. I.e.
the input contained inadmissible characters, or quotes were mismatched.
The Text
argument contains the parser error.
data TooFewParamsError Source
Too few parameters were given to a command. The first value is the minium, the second the actual number.
data TooManyParamsError Source
Too many parameters were given to a command. The first value is the maximum, the second the actual number.
Dealing with arguments
readArgs :: MonadThrow m => Text -> m [Text] Source
Splits and trims the input of a command. If the input cannot be parsed, a
MalformedParamsError
exception is thrown.
Format
Any non-whitespace sequence of characters is interpreted as one argument, unless double quotes (") are used, in which case they demarcate an argument. Each argument is parsed as a haskell string literal (quote-less arguments have quotes inserted around them).
Arguments are parsed using parsec's stringLiteral
(haskell-style),
meaning that escape sequences and unicode characters are handled automatically.
getName :: Text -> Maybe Text Source
Gets the first part of a command string. Returns Nothing
if the string is empty of if readArgs
throws a MalformedParamsError
.
The "default" command test for making commands.
This function uses getName
to extract the first part of the user input,
stripping whitespace and also checking whether the entire input is well-formed.
quoteArg :: Text -> Text Source
Surrounds an argument in quote marks, if necessary.
This is useful when arguments were extracted via readArgs
, which deletes
quote marks. Quotes are placed around the input iff it is empty or contains
whitespace.
Helpers
summarizeCommands :: MonadIO m => [Command m2 i z] -> m () Source
Prints out a list of command names, with their descriptions.
Making commands
Ignore the "a0"-type parameters in the Askers.
:: (MonadIO m, MonadCatch m, Monoid i) | |
=> Text | Command name. |
-> (i -> Bool) | Command test. |
-> Text | Command description. |
-> (i -> m z) | Command function. It will receive the first part of the input (customarily the command name), or the empty string if the input only contained whitespace. |
-> Command m i z |
Creates a command without parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input.
If True, running the command will run the Asker's
IO action if not enough input is provided. If False
a |
-> Asker m a0 a |
|
-> (Text -> a -> m z) | Command function. |
-> Command m Text z |
Creates a command with one parameter.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> (Text -> a -> b -> m z) | Command function. |
-> Command m Text z |
Creates a command with two parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> (Text -> a -> b -> c -> m z) | Command function. |
-> Command m Text z |
Creates a command with three parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> Asker m d0 d |
|
-> (Text -> a -> b -> c -> d -> m z) | Command function. |
-> Command m Text z |
Creates a command with four parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> Asker m d0 d |
|
-> Asker m e0 e |
|
-> (Text -> a -> b -> c -> d -> e -> m z) | Command function. |
-> Command m Text z |
Creates a command with five parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> Asker m d0 d |
|
-> Asker m e0 e |
|
-> Asker m f0 f |
|
-> (Text -> a -> b -> c -> d -> e -> f -> m z) | Command function. |
-> Command m Text z |
Creates a command with six parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> Asker m d0 d |
|
-> Asker m e0 e |
|
-> Asker m f0 f |
|
-> Asker m g0 g |
|
-> (Text -> a -> b -> c -> d -> e -> f -> g -> m z) | Command function. |
-> Command m Text z |
Creates a command with seven parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. |
-> Asker m a0 a |
|
-> Asker m b0 b |
|
-> Asker m c0 c |
|
-> Asker m d0 d |
|
-> Asker m e0 e |
|
-> Asker m f0 f |
|
-> Asker m g0 g |
|
-> Asker m h0 h |
|
-> (Text -> a -> b -> c -> d -> e -> f -> g -> h -> m z) | Command function. |
-> Command m Text z |
Creates a command with eight parameters.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> (Text -> Bool) | Command test. |
-> Text | Command description |
-> Bool | Whether the command can ask for input. This only affects the necessary parameters. |
-> [Asker m a0 a] |
|
-> [Asker m b0 a] |
|
-> (Text -> [a] -> m z) | |
-> Command m Text z |
Creates a command with a list of parameters.
The first list necc
of Asker
s indicates the necessary parameters;
the user must at least provide this many. The second list opt
contains
Asker
s for additional, optional parameters, and may be infinite.
If the number of passed parameters exceeds
length necc + length opt
, or if any Asker
fails,
the command returns an AskFailure
.
Example commands.
A few commands for convenience.
:: (MonadIO m, MonadCatch m) | |
=> Text | Command name. |
-> [Text] | Alternative names for the command. The user can either the command name or any of the alternative names. E.g. "exit" with alternative names ":e", ":quit". |
-> Command m Text () |
A command that takes no arguments and does nothing.
defExitCmd :: (MonadIO m, MonadCatch m) => Command m Text () Source
A command with the name ":exit" and the description "Exits the program." Otherwise, it does nothing.
You can use this as the exit-command for makeREPL
,
if no special clean-up is needed upon quitting.
defHelpCmd :: (MonadIO m, MonadCatch m, Foldable f) => f (Command m0 a b) -> Command m Text () Source
A help-command with the name ":help" and the description "Prints this help text."
It goes through the given list of commands and prints the name and description of each one.
defErrorHandler :: MonadIO m => [Handler m ()] Source
A default error handler that catches SomeREPLError
and prints it to stdout.
Useful in combination with makeREPL
.